home *** CD-ROM | disk | FTP | other *** search
/ Libris Britannia 4 / science library(b).zip / science library(b) / PROGRAMM / ASSEMBLE / H145.ZIP / ASXXXX_3.ZIP / BUF25.ASM next >
Assembly Source File  |  1990-07-18  |  101KB  |  4,986 lines

  1. ;*            buffalo
  2. ;* "bit user's fast friendly aid to logical operation"
  3. ;*
  4. ;* rev 2.0 - 4/23/85    - added disassembler.
  5. ;*            - variables now ptrn and tmpn.
  6. ;* rev 2.1 - 4/29/85    - added byte erase to chgbyt routine.
  7. ;* rev 2.2 - 5/16/85    - added hooks for evb board - acia
  8. ;*              drivers, init and host routines.
  9. ;*         7/8/85     - fixed dump wraparound problem.
  10. ;*         7/10/85    - added evm board commands.
  11. ;*            - added fill instruction.
  12. ;*         7/18/85    - added jump to eeprom.
  13. ;* rev 2.3 - 8/22/85     - call targco to disconnect sci from host
  14. ;*              in reset routine for evb board.
  15. ;*         10/3/85    - modified load for download through terminal.
  16. ;* rev 2.4 - 7/1/86    - changed dflop address to fix conflicts with
  17. ;*              eeprom.  (was at a000)
  18. ;* rev 2.5 - 9/8/86    - modified to provide additional protection from
  19. ;*              program run-away on power down.  also fixed bugs
  20. ;*              in mm and move.  changed to 1 stop bit from 2.
  21. ;*
  22. ;********************************************************
  23. ;*    although the information contained herein,    *
  24. ;*    as well as any information provided relative    *
  25. ;*    thereto, has been carefully reviewed and is    *
  26. ;*    believed accurate, motorola assumes no        *
  27. ;*    liability arising out of its application or    *
  28. ;*    use, neither does it convey any license under    *
  29. ;*    its patent rights nor the rights of others.    *
  30. ;********************************************************
  31.  
  32.     .area    BUF25    (ABS,OVR)
  33.  
  34.     .setdp
  35.  
  36. ;************************
  37. ;*    equates        *
  38. ;************************
  39.  
  40. rambs    =    0x0000        ; start of ram
  41. regbs    =    0x1000        ; start of registers
  42. rombs    =    0xe000        ; start of rom
  43. porte    =    regbs+0x0a    ; port e
  44. tcnt    =    regbs+0x0e    ; timer count
  45. toc5    =    regbs+0x1e    ; oc5 reg
  46. tctl1    =    regbs+0x20    ; timer control 1
  47. tmsk1    =    regbs+0x22    ; timer mask 1
  48. tflg1    =    regbs+0x23    ; timer flag 1
  49. tmsk2    =    regbs+0x24    ; timer mask 2
  50. baud    =    regbs+0x2b    ; sci baud reg
  51. sccr1    =    regbs+0x2c    ; sci control1 reg
  52. sccr2    =    regbs+0x2d    ; sci control2 reg
  53. scsr    =    regbs+0x2e    ; sci status reg
  54. scdat    =    regbs+0x2f    ; sci data reg
  55. option    =    regbs+0x39    ; option reg
  56. coprst    =    regbs+0x3a    ; cop reset reg
  57. pprog    =    regbs+0x3b    ; ee prog reg
  58. hprio    =    regbs+0x3c    ; hprio reg
  59. config    =    regbs+0x3f    ; config register
  60. dflop    =    0x4000        ; evb d flip flop
  61. duart    =    0xd000        ; duart address
  62. porta    =    duart
  63. portb    =    duart+8
  64. acia    =    0x9800        ; acia address
  65. prompt    =    '>
  66. bufflng    =    35
  67. ctla    =    0x01        ; exit host or assembler
  68. ctlb    =    0x02        ; send break to host
  69. ctlw    =    0x17        ; wait
  70. ctlx    =    0x18        ; abort
  71. del    =    0x7f        ; abort
  72. eot    =    0x04        ; end of text/table
  73. swi    =    0x3f
  74.  
  75. ;***************
  76. ;*     ram     *
  77. ;***************
  78.  
  79.     .org    0x36
  80.  
  81. ;*** buffalo ram space ***
  82.  
  83.     .blkb    20    ; user stack area
  84. ustack:    .blkb    30    ; monitor stack area
  85. stack:    .blkb    1
  86. inbuff:    .blkb    bufflng    ; input buffer
  87. endbuff    = .
  88. combuff:
  89.     .blkb    8    ; command buffer
  90. shftreg:
  91.     .blkb    2    ; input shift register
  92. brktabl:
  93.     .blkb    8    ; breakpoint table
  94. regs:    .blkb    9    ; user's pc,y,x,a,b,c
  95. sp:    .blkb    2    ; user's sp
  96. autolf:    .blkb    1    ; auto lf flag for i/o
  97. iodev:    .blkb    1    ; 0=sci,  1=acia, 2=duarta, 3=duartb
  98. extdev:    .blkb    1    ; 0=none, 1=acia, 2=duart,
  99. hostdev:
  100.     .blkb    1    ; 0=sci,  1=acia,        3=duartb
  101. count:    .blkb    1    ; # characters read
  102. ptrmem:    .blkb    2    ; current memory location
  103.  
  104. ;*** buffalo variables - used by: ***
  105. ptr0:    .blkb    2    ; main,readbuff,incbuff,as
  106. ptr1:    .blkb    2    ; main,br,du,mo,as
  107. ptr2:    .blkb    2    ; du,go,mo,as
  108. ptr3:    .blkb    2    ; ho,mo,as
  109. ptr4:    .blkb    2    ; go,as
  110. ptr5:    .blkb    2    ; as
  111. ptr6:    .blkb    2    ; go,as
  112. ptr7:    .blkb    2    ; go,as
  113. tmp1:    .blkb    1    ; main,hexbin,buffarg,termarg
  114. tmp2:    .blkb    1    ; go,ho,as
  115. tmp3:    .blkb    1    ; as
  116. tmp4:    .blkb    1    ; go,ho,me,as
  117.  
  118. ;*** vector jump table ***
  119. jsci:    .blkb    3
  120. jspi:    .blkb    3
  121. jpaie:    .blkb    3
  122. jpao:    .blkb    3
  123. jtof:    .blkb    3
  124. jtoc5:    .blkb    3
  125. jtoc4:    .blkb    3
  126. jtoc3:    .blkb    3
  127. jtoc2:    .blkb    3
  128. jtoc1:    .blkb    3
  129. jtic3:    .blkb    3
  130. jtic2:    .blkb    3
  131. jtic1:    .blkb    3
  132. jrti:    .blkb    3
  133. jirq:    .blkb    3
  134. jxirq:    .blkb    3
  135. jswi:    .blkb    3
  136. jillop:    .blkb    3
  137. jcop:    .blkb    3
  138. jclm:    .blkb    3
  139.  
  140. ;*****************
  141. ;*
  142. ;* rom starts here *
  143. ;*
  144. ;*****************
  145.  
  146.     .org    rombs
  147.  
  148. ;*****************
  149. ;**    buffalo - this is where buffalo starts
  150. ;** out of reset.  all initialization is done
  151. ;** here including determination of where the
  152. ;** user terminal is (sci,acia, or duart).
  153. ;*****************
  154.  
  155. buffalo:
  156.     ldx    #porte
  157.     brclr 0,x,#0x01,bufisit    ; if bit 0 of port e is 1
  158.     jmp    0xb600        ; then jump to the start of eeprom
  159. bufisit:
  160.     ldaa    #0x93
  161.     staa    option        ; adpu, dly, irqe, cop
  162.     ldaa    #0x00
  163.     staa    tmsk2        ; timer pre = %1 for trace
  164.     lds    #stack        ; monitor stack pointer
  165.     jsr    vecinit
  166.     ldx    #ustack
  167.     stx    *sp        ; default user stack
  168.     ldaa    #0xd0
  169.     staa    *regs+8        ; default user ccr
  170.     ldd    #0x3f0d        ; initial command is ?
  171.     std    *inbuff
  172.     jsr    bpclr        ; clear breakpoints
  173.     clr    *autolf
  174.     inc    *autolf        ; auto cr/lf = on
  175.  
  176. ;* determine type of external comm device - none, or acia *
  177.  
  178.     clr    *extdev        ; default is none
  179.     ldaa    hprio
  180.     anda    #0x20
  181.     beq    buff2        ; jump if single chip mode
  182.     ldaa    #0x03        ; see if external acia exists
  183.     staa    acia        ; master reset
  184.     ldaa    acia
  185.     anda    #0x7f        ; mask irq bit from status register
  186.     bne    buff1        ; jump if status reg not 0
  187.     ldaa    #0x12
  188.     staa    acia        ; turn on acia
  189.     ldaa    acia
  190.     anda    #0x02
  191.     beq    buff1        ; jump if tdre not set
  192.     ldaa    #0x01
  193.     staa    *extdev        ; external device is acia
  194.     bra    buff2
  195.  
  196. buff1    = .            ; see if duart exists
  197.     ldaa    duart+0x0c    ; read irq vector register
  198.     cmpa    #0x0f        ; should be out of reset
  199.     bne    buff2
  200.     ldaa    #0xaa
  201.     staa    duart+0x0c    ; write irq vector register
  202.     ldaa    duart+0x0c    ; read irq vector register
  203.     cmpa    #0xaa
  204.     bne    buff2
  205.     ldaa    #0x02
  206.     staa    *extdev        ; external device is duart a
  207.  
  208. ;* find terminal port - sci or external. *
  209.  
  210. buff2:    clr    *iodev
  211.     jsr    targco        ; disconnect sci for evb board
  212.     jsr    signon        ; initialize sci
  213.     ldaa    *extdev
  214.     beq    buff3        ; jump if no external device
  215.     staa    *iodev
  216.     jsr    signon        ; initialize external device
  217. buff3:    clr    *iodev
  218.     jsr    input        ; get input from sci port
  219.     cmpa    #0x0d
  220.     beq    buff4        ; jump if cr - sci is terminal port
  221.     ldaa    *extdev
  222.     beq    buff3        ; jump if no external device
  223.     staa    *iodev
  224.     jsr    input        ; get input from external device
  225.     cmpa    #0x0d
  226.     beq    buff4        ; jump if cr - terminal found ext
  227.     bra    buff3
  228.  
  229. signon:    jsr    init        ; initialize device
  230.     ldx    #msg1        ; buffalo message
  231.     jsr    outstrg
  232.     rts
  233.  
  234. ;* determine where host port should be.
  235.  
  236. buff4:    clr    *hostdev        ; default - host = sci port
  237.     ldaa    *iodev
  238.     cmpa    #0x01
  239.     beq    buff5        ; default host if term = acia
  240.     ldaa    #0x03
  241.     staa    *hostdev        ; else host is duart port b
  242. buff5    = .
  243.  
  244. ;*****************
  245. ;**    main - this module reads the user's input into
  246. ;** a buffer called inbuff.  the first field (assumed
  247. ;** to be the command field) is then parsed into a
  248. ;** second buffer called combuff.  the command table
  249. ;** is then searched for the contents of combuff and
  250. ;** if found, the address of the corresponding task
  251. ;** routine is fetched from the command table.  the
  252. ;** task is then called as a subroutine so that
  253. ;** control returns back to here upon completion of
  254. ;** the task.  buffalo expects the following format
  255. ;** for commands:
  256. ;**    <cmd>[<wsp><arg><wsp><arg>...]<cr>
  257. ;** [] implies contents optional.
  258. ;** <wsp> means whitespace character (space,comma,tab).
  259. ;** <cmd> = command string of 1-8 characters.
  260. ;** <arg> = argument particular to the command.
  261. ;** <cr> = carriage return signifying end of input string.
  262. ;*****************
  263. ;* prompt user
  264. ;*do
  265. ;*    a=input();
  266. ;*    if(a==(cntlx or del)) continue;
  267. ;*    elseif(a==backspace)
  268. ;*    b--;
  269. ;*    if(b<0) b=0;
  270. ;*    else
  271. ;*    if(a==cr && buffer empty)
  272. ;*        repeat last command;
  273. ;*    else put a into buffer;
  274. ;*        check if buffer full;
  275. ;*while(a != (cr or /)
  276.  
  277. main:    lds    #stack        ; initialize sp every time
  278.     clr    *autolf
  279.     inc    *autolf        ; auto cr/lf = on
  280.     jsr    outcrlf
  281.     ldaa    #prompt        ; prompt user
  282.     jsr    output
  283.     clrb
  284. main1:    jsr    inchar        ; read terminal
  285.     ldx    #inbuff
  286.     abx            ; pointer into buffer
  287.     cmpa    #ctlx
  288.     beq    main        ; jump if cntl x
  289.     cmpa    #del
  290.     beq    main        ; jump if del
  291.     cmpa    #0x08
  292.     bne    main2        ; jump if not bckspc
  293.     decb
  294.     blt    main        ; jump if buffer empty
  295.     bra    main1
  296. main2:    cmpa    #0xd
  297.     bne    main3        ; jump if not cr
  298.     tstb
  299.     beq    comm0        ; jump if buffer empty
  300.     staa    ,x        ; put a in buffer
  301.     bra    comm0
  302. main3:    staa    ,x        ; put a in buffer
  303.     incb
  304.     cmpb    #bufflng
  305.     ble    main4        ; jump if not long
  306.     ldx    #msg3        ; "long"
  307.     jsr    outstrg
  308.     bra    main
  309. main4:    cmpa    #'/
  310.     bne    main1        ; jump if not "/"
  311. ;*    *******************
  312.  
  313. ;*****************
  314. ;*    parse out and evaluate the command field.
  315. ;*****************
  316. ;*initialize
  317.  
  318. comm0    = .
  319.     clr    *tmp1        ; enable "/" command
  320.     clr    *shftreg
  321.     clr    *shftreg+1
  322.     clrb
  323.     ldx    #inbuff        ; ptrbuff[] = inbuff[]
  324.     stx    *ptr0
  325.     jsr    wskip        ; find first char
  326.  
  327. ;*while((a=readbuff) != (cr or wspace))
  328. ;*    upcase(a);
  329. ;*    buffptr[b] = a
  330. ;*    b++
  331. ;*    if (b > 8) error(too long);
  332. ;*    if(a == "/")
  333. ;*        if(enabled) mslash();
  334. ;*        else error(command?);
  335. ;*    else hexbin(a);
  336.  
  337. comm1    = .
  338.     jsr    readbuff    ; read from buffer
  339.     ldx    #combuff
  340.     abx
  341.     jsr    upcase        ; convert to upper case
  342.     staa    ,x        ; put in command buffer
  343.     cmpa    #0x0d
  344.     beq    srch        ; jump if cr
  345.     jsr    wchek
  346.     beq    srch        ; jump if wspac
  347.     jsr    incbuff        ; move buffer pointer
  348.     incb
  349.     cmpb    #0x8
  350.     ble    comm2
  351.     ldx    #msg3        ; "long"
  352.     jsr    outstrg
  353.     jmp    main
  354.  
  355. comm2    = .
  356.     cmpa    #'/
  357.     bne    comm4        ; jump if not "/"
  358.     tst    *tmp1
  359.     bne    comm3        ; jump if not enabled
  360.     stab    *count
  361.     ldx    #mslash
  362.     jmp    exec        ; execute "/"
  363. comm3:    ldx    #msg8        ; "command?"
  364.     jsr    outstrg
  365.     jmp    main
  366. comm4    = .
  367.     jsr    hexbin
  368.     bra    comm1
  369.  
  370. ;*****************
  371. ;*    search tables for command.    at this point,
  372. ;* combuff holds the command field to be executed,
  373. ;* and b =    # of characters in the command field.
  374. ;* the command table holds the whole command name
  375. ;* but only the first n characters of the command
  376. ;* must match what is in combuff where n is the
  377. ;* number of characters entered by the user.
  378. ;*****************
  379. ;*count = b;
  380. ;*ptr1 = comtabl;
  381. ;*while(ptr1[0] != end of table)
  382. ;*    ptr1 = next entry
  383. ;*    for(b=1; b=count; b++)
  384. ;*    if(ptr1[b] == combuff[b]) continue;
  385. ;*    else error(not found);
  386. ;*    execute task;
  387. ;*    return();
  388. ;*return(command not found);
  389.  
  390. srch:    stab    *count        ; size of command entered
  391.     ldx    #comtabl    ; pointer to table
  392.     stx    *ptr1        ; pointer to next entry
  393. srch1:    ldx    *ptr1
  394.     ldy    #combuff    ; pointer to command buffer
  395.     ldab    0,x
  396.     cmpb    #0xff
  397.     bne    srch2
  398.     ldx    #msg2        ; "command not found"
  399.     jsr    outstrg
  400.     jmp    main
  401. srch2:    pshx            ; compute next table entry
  402.     addb    #0x3
  403.     abx
  404.     stx    *ptr1
  405.     pulx
  406.     clrb
  407. srchlp:    incb            ; match characters loop
  408.     ldaa    1,x        ; read table
  409.     cmpa    0,y        ; compare to combuff
  410.     bne    srch1        ; try next entry
  411.     inx            ; move pointers
  412.     iny
  413.     cmpb    *count
  414.     blt    srchlp        ; loop countu1 times
  415.     ldx    *ptr1
  416.     dex
  417.     dex
  418.     ldx    0,x        ; jump address from table
  419. exec:    jsr    0,x        ; call task as subroutine
  420.     jmp    main
  421. ;*
  422. ;*****************
  423. ;*    utility subroutines - these routines
  424. ;* are called by any of the task routines.
  425. ;*****************
  426. ;*****************
  427. ;*    upcase(a) - if the contents of a is alpha,
  428. ;* returns a converted to uppercase.
  429. ;*****************
  430. upcase:    cmpa    #'a
  431.     blt    upcase1        ; jump if < a
  432.     cmpa    #'z
  433.     bgt    upcase1        ; jump if > z
  434.     suba    #0x20        ; convert
  435. upcase1:
  436.     rts
  437.  
  438. ;*****************
  439. ;*    bpclr() - clear all entries in the
  440. ;* table of breakpoints.
  441. ;*****************
  442. bpclr:    ldx    #brktabl
  443.     ldab    #8
  444. bpclr1:    clr    0,x
  445.     inx
  446.     decb
  447.     bgt    bpclr1        ; loop 8 times
  448.     rts
  449.  
  450. ;*****************
  451. ;*    rprnt1(x) - prints name and contents of a single
  452. ;* user register. on entry x points to name of register
  453. ;* in reglist.  on exit, a=register name.
  454. ;*****************
  455. reglist:
  456.     .ascii    'PYXABCS'    ; names
  457.     .byte    0,2,4,6,7,8,9    ; offset
  458.     .byte    1,1,1,0,0,0,1    ; size
  459.  
  460. rprnt1:    ldaa    0,x
  461.     psha
  462.     pshx
  463.     jsr    output        ; name
  464.     ldaa    #'-
  465.     jsr    output        ; dash
  466.     ldab    7,x        ; contents offset
  467.     ldaa    14,x        ; bytesize
  468.     ldx    #regs        ; address
  469.     abx
  470.     tsta
  471.     beq    rprn2        ; jump if 1 byte
  472.     jsr    out1byt        ; 2 bytes
  473. rprn2:    jsr    out1bsp
  474.     pulx
  475.     pula
  476.     rts
  477.  
  478. ;*****************
  479. ;*    rprint() - print the name and contents
  480. ;* of all the user registers.
  481. ;*****************
  482. rprint:    pshx
  483.     ldx    #reglist
  484. rpri1:    jsr    rprnt1        ; print name
  485.     inx
  486.     cmpa    #'S        ; s is last register
  487.     bne    rpri1        ; jump if not done
  488.     pulx
  489.     rts
  490.  
  491. ;*****************
  492. ;*    hexbin(a) - convert the ascii character in a
  493. ;* to binary and shift into shftreg.  returns value
  494. ;* in tmp1 incremented if a is not hex.
  495. ;*****************
  496. hexbin:    psha
  497.     pshb
  498.     pshx
  499.     jsr    upcase        ; convert to upper case
  500.     cmpa    #'0
  501.     blt    hexnot        ; jump if a < 0x30
  502.     cmpa    #'9
  503.     ble    hexnmb        ; jump if 0-9
  504.     cmpa    #'A
  505.     blt    hexnot        ; jump if 0x39> a <0x41
  506.     cmpa    #'F
  507.     bgt    hexnot        ; jump if a > 0x46
  508.     adda    #0x9        ; convert 0xa-0xf
  509. hexnmb:    anda    #0x0f        ; convert to binary
  510.     ldx    #shftreg
  511.     ldab    #4
  512. hexshft:
  513.     asl    1,x        ; 2 byte shift through
  514.     rol    0,x        ; carry bit
  515.     decb
  516.     bgt    hexshft        ; shift 4 times
  517.     oraa    1,x
  518.     staa    1,x
  519.     bra    hexrts
  520. hexnot:    inc    *tmp1        ; indicate not hex
  521. hexrts:    pulx
  522.     pulb
  523.     pula
  524.     rts
  525.  
  526. ;*****************
  527. ;*    buffarg() - build a hex argument from the
  528. ;* contents of the input buffer. characters are
  529. ;* converted to binary and shifted into shftreg
  530. ;* until a non-hex character is found.  on exit
  531. ;* shftreg holds the last four digits read, count
  532. ;* holds the number of digits read, ptrbuff points
  533. ;* to the first non-hex character read, and a holds
  534. ;* that first non-hex character.
  535. ;*****************
  536. ;*initialize
  537. ;*while((a=readbuff()) not hex)
  538. ;*    hexbin(a);
  539. ;*return();
  540.  
  541. buffarg:
  542.     clr    *tmp1        ; not hex indicator
  543.     clr    *count        ; # or digits
  544.     clr    *shftreg
  545.     clr    *shftreg+1
  546.     jsr    wskip
  547. bufflp:    jsr    readbuff    ; read char
  548.     jsr    hexbin
  549.     tst    *tmp1
  550.     bne    buffrts        ; jump if not hex
  551.     inc    *count
  552.     jsr    incbuff        ; move buffer pointer
  553.     bra    bufflp
  554. buffrts:
  555.     rts
  556.  
  557. ;*****************
  558. ;*    termarg() - build a hex argument from the
  559. ;* terminal.  characters are converted to binary
  560. ;* and shifted into shftreg until a non-hex character
  561. ;* is found.  on exit shftreg holds the last four
  562. ;* digits read, count holds the number of digits
  563. ;* read, and a holds the first non-hex character.
  564. ;*****************
  565. ;*initialize
  566. ;*while((a=inchar()) == hex)
  567. ;*    if(a = cntlx or del)
  568. ;*        abort;
  569. ;*    else
  570. ;*        hexbin(a); countu1++;
  571. ;*return();
  572.  
  573. termarg:
  574.     clr    *count
  575.     clr    *shftreg
  576.     clr    *shftreg+1
  577. term0:    jsr    inchar
  578.     cmpa    #ctlx
  579.     beq    term1        ; jump if controlx
  580.     cmpa    #del
  581.     bne    term2        ; jump if not delete
  582. term1:    jmp    main        ; abort
  583. term2:    clr    *tmp1        ; hex indicator
  584.     jsr    hexbin
  585.     tst    *tmp1
  586.     bne    term3        ; jump if not hex
  587.     inc    *count
  588.     bra    term0
  589. term3:    rts
  590.  
  591. ;*****************
  592. ;*    chgbyt() - if shftreg is not empty, put
  593. ;* contents of shftreg at address in x.    if x
  594. ;* is an address in eeprom then program it.
  595. ;*****************
  596. ;*if(count != 0)
  597. ;*    (x) = a;
  598. ;*    if(((x) != a) && (x == eeprom location))
  599. ;*    if((x) != 0xff) byte erase (x);
  600. ;*    if(a != 0xff) program(x) = a);
  601. ;*    if((x) != a) error(rom)
  602. ;*return;
  603.  
  604. chgbyt:    tst    *count
  605.     beq    chgbyt4        ; jump if shftreg empty
  606.     ldaa    *shftreg+1
  607.     staa    0,x        ; attempt to write
  608.     ldaa    0,x
  609.     cmpa    *shftreg+1
  610.     beq    chgbyt3        ; jump if it worked
  611.     cpx    #config
  612.     beq    chgbyt1        ; jump if config reg
  613.     cpx    #0xb600
  614.     blo    chgbyt3        ; jump if not ee
  615.     cpx    #0xb7ff
  616.     bhi    chgbyt3        ; jump if not ee
  617. chgbyt1    = .
  618.     ldaa    0,x
  619.     cmpa    #0xff
  620.     beq    chgbyt2        ; jump if already erased
  621.     ldaa    #0x16        ; do byte erase
  622.     staa    pprog
  623.     ldaa    #0xff
  624.     staa    0,x
  625.     ldaa    #0x17
  626.     bne    acl1
  627.     clra            ; fail safe
  628. acl1:    staa    pprog
  629.     bsr    chgwait
  630.     ldaa    #0x00
  631.     staa    pprog        ; end of byte erase
  632. chgbyt2    = .
  633.     ldaa    *shftreg+1
  634.     cmpa    #0xff
  635.     beq    chgbyt3        ; jump if no need to program
  636.     ldaa    #0x02        ; do byte program
  637.     staa    pprog
  638.     ldaa    *shftreg+1
  639.     staa    0,x
  640.     ldaa    #0x03
  641.     bne    acl2
  642.     clra            ; fail safe
  643. acl2:    staa    pprog
  644.     bsr    chgwait
  645.     ldaa    #0x00
  646.     staa    pprog        ; end of byte program
  647. chgbyt3    = .
  648.     ldaa    ,x
  649.     cmpa    *shftreg+1
  650.     beq    chgbyt4
  651.     pshx
  652.     ldx    #msg6        ; "rom"
  653.     jsr    outstrg
  654.     jsr    outcrlf
  655.     pulx
  656. chgbyt4    = .
  657.     rts
  658.  
  659. chgwait    = .         ; delay 10 ms at E = 2mhz
  660.     pshx
  661.     ldx    #0x0d06
  662. chgwait1:
  663.     dex
  664.     bne    chgwait1
  665.     pulx
  666.     rts
  667.  
  668. ;*****************
  669. ;*    readbuff() -  read the character in inbuff
  670. ;* pointed at by ptrbuff into a.  returns ptrbuff
  671. ;* unchanged.
  672. ;*****************
  673. readbuff:
  674.     pshx
  675.     ldx    *ptr0
  676.     ldaa    0,x
  677.     pulx
  678.     rts
  679.  
  680. ;*****************
  681. ;*    incbuff(), decbuff() - increment or decrement
  682. ;* ptrbuff.
  683. ;*****************
  684. incbuff:
  685.     pshx
  686.     ldx    *ptr0
  687.     inx
  688.     bra    incdec
  689. decbuff:
  690.     pshx
  691.     ldx    *ptr0
  692.     dex
  693. incdec:    stx    *ptr0
  694.     pulx
  695.     rts
  696.  
  697. ;*****************
  698. ;*    wskip() - read from the inbuff until a
  699. ;* non whitespace (space, comma, tab) character
  700. ;* is found.  returns ptrbuff pointing to the
  701. ;* first non-whitespace character and a holds
  702. ;* that character.
  703. ;*****************
  704. wskip:    jsr    readbuff    ; read character
  705.     jsr    wchek
  706.     bne    wskip1        ; jump if not wspc
  707.     jsr    incbuff        ; move pointer
  708.     bra    wskip        ; loop
  709. wskip1:    rts
  710.  
  711. ;*****************
  712. ;*    wchek(a) - returns z=1 if a holds a
  713. ;* whitespace character, else z=0.
  714. ;*****************
  715. wchek:    cmpa    #0x2c        ; comma
  716.     beq    wchek1
  717.     cmpa    #0x20        ; space
  718.     beq    wchek1
  719.     cmpa    #0x09        ; tab
  720. wchek1:    rts
  721.  
  722. ;*****************
  723. ;*    dchek(a) - returns z=1 if a = whitespace
  724. ;* or carriage return.    else returns z=0.
  725. ;*****************
  726. dchek:    jsr    wchek
  727.     beq    dchek1        ; jump if whitespace
  728.     cmpa    #0x0d
  729. dchek1:    rts
  730.  
  731. ;*****************
  732. ;*    chkabrt() - checks for a control x or delete
  733. ;* from the terminal.  if found, the stack is
  734. ;* reset and the control is transferred to main.
  735. ;* note that this is an abnormal termination.
  736. ;*    if the input from the terminal is a control w
  737. ;* then this routine keeps waiting until any other
  738. ;* character is read.
  739. ;*****************
  740. ;*a=input();
  741. ;*if(a=cntl w) wait until any other key;
  742. ;*if(a = cntl x or del) abort;
  743.  
  744. chkabrt:
  745.     jsr    input
  746.     beq    chk4        ; jump if no input
  747.     cmpa    #ctlw
  748.     bne    chk2        ; jump in not cntlw
  749. chkabrt1:
  750.     jsr    input
  751.     beq    chkabrt1    ; jump if no input
  752. chk2:    cmpa    #del
  753.     beq    chk3        ; jump if delete
  754.     cmpa    #ctlx
  755.     beq    chk3        ; jump if control x
  756.     cmpa    #ctla
  757.     bne    chk4        ; jump not control a
  758. chk3:    jmp    main        ; abort
  759. chk4:    rts            ; return
  760.  
  761. ;***********************
  762. ;*    hostco - connect sci to host for evb board.
  763. ;*    targco - connect sci to target for evb board.
  764. ;***********************
  765. hostco:    psha
  766.     ldaa    #0x01
  767.     staa    dflop        ; send 1 to d-flop
  768.     pula
  769.     rts
  770.  
  771. targco:    psha
  772.     ldaa    #0x00
  773.     staa    dflop        ; send 0 to d-flop
  774.     pula
  775.     rts
  776.  
  777. ;*
  778. ;**********
  779. ;*
  780. ;*    vecinit - this routine checks for
  781. ;*    vectors in the ram table.    all
  782. ;*    uninitialized vectors are programmed
  783. ;*    to jmp stopit
  784. ;*
  785. ;**********
  786. ;*
  787. vecinit:
  788.     ldx    #jsci        ; point to first ram vector
  789.     ldy    #stopit        ; pointer to stopit routine
  790.     ldd    #0x7e03        ; a=jmp opcode; b=offset
  791. vecloop:
  792.     cmpa    0,x
  793.     beq    vecnext        ; if vector already in
  794.     staa    0,x        ; install jmp
  795.     sty    1,x        ; to stopit routine
  796. vecnext:
  797.     abx            ; add 3 to point at next vector
  798.     cpx    #jclm+3        ; done?
  799.     bne    vecloop        ; if not, continue loop
  800.     rts
  801. ;*
  802. stopit:    ldaa    #0x50        ; stop-enable; irq, xirq-off
  803.     tap
  804.     stop            ; you are lost!    shut down
  805.     jmp    stopit        ; in case continue by xirq
  806.  
  807. ;**********
  808. ;*
  809. ;*    i/o module
  810. ;*    communications with the outside world.
  811. ;* 3 i/o routines (init, input, and output) call
  812. ;* drivers specified by iodev (0=sci, 1=acia,
  813. ;* 2=duarta, 3=duartb).
  814. ;*
  815. ;**********
  816. ;*    init() - initialize device specified by iodev.
  817. ;*********
  818. ;*
  819. init    = .
  820.     psha            ; save registers
  821.     pshx
  822.     ldaa    *iodev
  823.     cmpa    #0x00
  824.     bne    init1        ; jump not sci
  825.     jsr    onsci        ; initialize sci
  826.     bra    init4
  827. init1:    cmpa    #0x01
  828.     bne    init2        ; jump not acia
  829.     jsr    onacia        ; initialize acia
  830.     bra    init4
  831. init2:    ldx    #porta
  832.     cmpa    #0x02
  833.     beq    init3        ; jump duart a
  834.     ldx    #portb
  835. init3:    jsr    onuart        ; initialize duart
  836. init4:    pulx            ; restore registers
  837.     pula
  838.     rts
  839.  
  840. ;**********
  841. ;*    input() - read device. returns a=char or 0.
  842. ;*    this routine also disarms the cop.
  843. ;**********
  844. input    = .
  845.     pshx
  846.     ldaa    #0x55        ; reset cop
  847.     staa    coprst
  848.     ldaa    #0xaa
  849.     staa    coprst
  850.     ldaa    *iodev
  851.     bne    input1        ; jump not sci
  852.     jsr    insci        ; read sci
  853.     bra    input4
  854. input1:    cmpa    #0x01
  855.     bne    input2        ; jump not acia
  856.     jsr    inacia        ; read acia
  857.     bra    input4
  858. input2:    ldx    #porta
  859.     cmpa    #0x02
  860.     beq    input3        ; jump if duart a
  861.     ldx    #portb
  862. input3:    jsr    inuart        ; read uart
  863. input4:    pulx
  864.     rts
  865.  
  866. ;**********
  867. ;*    output() - output character in a.
  868. ;**********
  869.  
  870. output    = .
  871.     psha            ; save registers
  872.     pshb
  873.     pshx
  874.     ldab    *iodev
  875.     bne    output1        ; jump not sci
  876.     jsr    outsci        ; write sci
  877.     bra    output4
  878. output1:
  879.     cmpb    #0x01
  880.     bne    output4        ; jump not acia
  881.     jsr    outacia        ; write acia
  882.     bra    output4
  883. output2:
  884.     ldx    #porta
  885.     cmpb    #0x02
  886.     beq    output3        ; jump if duart a
  887.     ldx    #portb
  888. output3:
  889.     jsr    outuart        ; write uart
  890. output4:
  891.     pulx
  892.     pulb
  893.     pula
  894.     rts
  895.  
  896. ;**********
  897. ;*    onuart(port) - initialize a duart port.
  898. ;* sets duart to internal clock, divide by 16,
  899. ;* 8 data + 1 stop bits.
  900. ;**********
  901.  
  902. onuart:    ldaa    #0x22
  903.     staa    2,x        ; reset receiver
  904.     ldaa    #0x38
  905.     staa    2,x        ; reset transmitter
  906.     ldaa    #0x40
  907.     staa    2,x        ; reset error status
  908.     ldaa    #0x10
  909.     staa    2,x        ; reset pointer
  910.     ldaa    #0x00
  911.     staa    duart+4        ; clock source
  912.     ldaa    #0x00
  913.     staa    duart+5        ; interrupt mask
  914.     ldaa    #0x13
  915.     staa    0,x        ; 8 data, no parity
  916.     ldaa    #0x07
  917.     staa    0,x        ; 1 stop bits
  918.     ldaa    #0xbb        ; baud rate (9600)
  919.     staa    1,x        ; tx and rcv baud rate
  920.     ldaa    #0x05
  921.     staa    2,x        ; enable tx and rcv
  922.     rts
  923.  
  924. ;**********
  925. ;*    inuart(port) - check duart for any input.
  926. ;**********
  927.  
  928. inuart:    ldaa    1,x        ; read status
  929.     anda    #0x01        ; check rdrf
  930.     beq    inuart1        ; jump if no data
  931.     ldaa    3,x        ; read data
  932.     anda    #0x7f        ; to mask parity
  933. inuart1:
  934.     rts
  935.  
  936. ;**********
  937. ;*    outuart(port) - output the character in a.
  938. ;*    if autolf=1, transmits cr or lf as crlf.
  939. ;**********
  940. outuart:
  941.     tst    *autolf
  942.     beq    outuart2    ; jump if no autolf
  943.     bsr    outuart2
  944.     cmpa    #0x0d
  945.     bne    outuart1
  946.     ldaa    #0x0a        ; if cr, output lf
  947.     bra    outuart2
  948. outuart1:
  949.     cmpa    #0x0a
  950.     bne    outuart3
  951.     ldaa    #0x0d        ; if lf, output cr
  952. outuart2:
  953.      ldab    1,x        ; check status
  954.     andb    #0x4
  955.     beq    outuart2    ; loop until tdre=1
  956.     anda    #0x7f        ; mask parity
  957.     staa    3,x        ; send character
  958. outuart3:
  959.     rts
  960.  
  961. ;**********
  962. ;*    onsci() - initialize the sci for 9600
  963. ;*            baud at 8 mhz extal.
  964. ;**********
  965. onsci:    ldaa    #0x30
  966.     staa    baud        ; baud register
  967.     ldaa    #0x00
  968.     staa    sccr1
  969.     ldaa    #0x0c
  970.     staa    sccr2        ; enable
  971.     rts
  972.  
  973. ;**********
  974. ;*    insci() - read from sci.    return a=char or 0.
  975. ;**********
  976. insci:    ldaa    scsr        ; read status reg
  977.     anda    #0x20
  978.     beq    insci1        ; jump if rdrf=0
  979.     ldaa    scdat        ; read data register
  980.     anda    #0x7f        ; mask parity
  981. insci1:    rts
  982.  
  983. ;**********
  984. ;*    outsci() - output a to sci. if autolf = 1,
  985. ;*        cr and lf sent as crlf.
  986. ;**********
  987. outsci:    tst    *autolf
  988.     beq    outsci2        ; jump if autolf=0
  989.     bsr    outsci2
  990.     cmpa    #0x0d
  991.     bne    outsci1
  992.     ldaa    #0x0a        ; if cr, send lf
  993.     bra    outsci2
  994. outsci1:
  995.     cmpa    #0x0a
  996.     bne    outsci3
  997.     ldaa    #0x0d        ; if lf, send cr
  998. outsci2:
  999.     ldab    scsr        ; read status
  1000.     bitb    #0x80
  1001.     beq    outsci2        ; loop until tdre=1
  1002.     anda    #0x7f        ; mask parity
  1003.     staa    scdat        ; send character
  1004. outsci3:
  1005.     rts
  1006.  
  1007. ;**********
  1008. ;*    onacia - initialize the acia for
  1009. ;* 8 data bits, 1 stop bit, divide by 64 clock.
  1010. ;**********
  1011. onacia:    ldx    #acia
  1012.     ldaa    #0x03
  1013.     staa    0,x        ; master reset
  1014.     ldaa    #0x16
  1015.     staa    0,x        ; setup
  1016.     rts
  1017.  
  1018. ;**********
  1019. ;*    inacia - read from the acia, return a=char or 0.
  1020. ;**********
  1021. inacia:    ldx    #acia
  1022.     ldaa    0,x        ; status
  1023.     psha
  1024.     anda    #0x70        ; check pe, ov, fe
  1025.     pula
  1026.     beq    inacia1        ; jump - no error
  1027.     bsr    onacia        ; reinitialize and try again
  1028.     bra    inacia
  1029. inacia1:
  1030.     lsra            ; check rdrf
  1031.     bcs    inacia2        ; jump if data
  1032.     clra            ; return(no data)
  1033.     rts
  1034. inacia2:
  1035.     ldaa    1,x        ; read data
  1036.     anda    #0x7f        ; mask parity
  1037.     rts
  1038.  
  1039. ;**********
  1040. ;*    outacia - output a to acia. if autolf = 1,
  1041. ;*        cr or lf sent as crlf.
  1042. ;**********
  1043. outacia:
  1044.     bsr    outacia3    ; output char
  1045.     tst    *autolf
  1046.     beq    outacia2    ; jump no autolf
  1047.     cmpa    #0x0d
  1048.     bne    outacia1
  1049.     ldaa    #0x0a
  1050.     bsr    outacia3    ; if cr, output lf
  1051.     bra    outacia2
  1052. outacia1:
  1053.     cmpa    #0x0a
  1054.     bne    outacia2
  1055.     ldaa    #0x0d
  1056.     bsr    outacia3    ; if lf, output cr
  1057. outacia2:
  1058.     rts
  1059.  
  1060. outacia3:
  1061.     ldx    #acia
  1062.     ldab    0,x
  1063.     bitb    #0x2
  1064.     beq    outacia3    ; loop until tdre
  1065.     anda    #0x7f        ; mask parity
  1066.     staa    1,x        ; output
  1067.     rts
  1068. ;*
  1069. ;*    space for modifying outacia routine
  1070. ;*
  1071.     .word    0xffff,0xffff,0xffff,0xffff
  1072. ;*******************************
  1073. ;*** i/o utility subroutines ***
  1074. ;***these subroutines perform the neccesary
  1075. ;* data i/o operations.
  1076. ;* outlhlf-convert left 4 bits of a from binary
  1077. ;*        to ascii and output.
  1078. ;* outrhlf-convert right 4 bits of a from binary
  1079. ;*        to ascii and output.
  1080. ;* out1byt-convert byte addresed by x from binary
  1081. ;*        to ascii and output.
  1082. ;* out1bsp-convert byte addressed by x from binary
  1083. ;*        to ascii and output followed by a space.
  1084. ;* out2bsp-convert 2 bytes addressed by x from binary
  1085. ;*        to ascii and  output followed by a space.
  1086. ;* outspac-output a space.
  1087. ;*
  1088. ;* outcrlf-output a line feed and carriage return.
  1089. ;*
  1090. ;* outstrg-output the string of ascii bytes addressed
  1091. ;*        by x until 0x04.
  1092. ;* outa-output the ascii character in a.
  1093. ;*
  1094. ;* inchar-input to a and echo one character.  loops
  1095. ;*        until character read.
  1096. ;********************
  1097.  
  1098. ;**********
  1099. ;*    outrhlf(), outlhlf(), outa()
  1100. ;*convert a from binary to ascii and output.
  1101. ;*contents of a are destroyed..
  1102. ;**********
  1103. outlhlf:
  1104.     lsra            ; shift data to right
  1105.     lsra
  1106.     lsra
  1107.     lsra
  1108. outrhlf:
  1109.     anda    #0x0f        ; mask top half
  1110.     adda    #0x30        ; convert to ascii
  1111.     cmpa    #0x39
  1112.     ble    outa        ; jump if 0-9
  1113.     adda    #0x07        ; convert to hex a-f
  1114. outa:    jsr    output        ; output character
  1115.     rts
  1116.  
  1117. ;**********
  1118. ;*    out1byt(x) - convert the byte at x to two
  1119. ;* ascii characters and output. return x pointing
  1120. ;* to next byte.
  1121. ;**********
  1122. out1byt:
  1123.     psha
  1124.     ldaa    0,x        ; get data in a
  1125.     psha            ; save copy
  1126.     bsr    outlhlf        ; output left half
  1127.     pula            ; retrieve copy
  1128.     bsr    outrhlf        ; output right half
  1129.     pula
  1130.     inx
  1131.     rts
  1132.  
  1133. ;**********
  1134. ;*    out1bsp(x), out2bsp(x) - output 1 or 2 bytes
  1135. ;* at x followed by a space.  returns x pointing to
  1136. ;* next byte.
  1137. ;**********
  1138. out2bsp:
  1139.     jsr    out1byt        ; do first byte
  1140. out1bsp:
  1141.     jsr    out1byt        ; do next byte
  1142. outspac:
  1143.     ldaa    #0x20        ; output a space
  1144.     jsr    output
  1145.     rts
  1146.  
  1147. ;**********
  1148. ;*    outcrlf() - output a carriage return and
  1149. ;* a line feed.    returns a = cr.
  1150. ;**********
  1151. outcrlf:
  1152.     ldaa    #0x0d        ; cr
  1153.     jsr    output        ; output a
  1154.     ldaa    #0x00
  1155.     jsr    output        ; output padding
  1156.     ldaa    #0x0d
  1157.     rts
  1158.  
  1159. ;**********
  1160. ;*    outstrg(x) - output string of ascii bytes
  1161. ;* starting at x until end of text (0x04).    can
  1162. ;* be paused by control w (any char restarts).
  1163. ;**********
  1164. outstrg:
  1165.     jsr    outcrlf
  1166. outstrg0:
  1167.     psha
  1168. outstrg1:
  1169.     ldaa    0,x        ; read char into a
  1170.     cmpa    #eot
  1171.     beq    outstrg3    ; jump if eot
  1172.     jsr    output        ; output character
  1173.     inx
  1174.     jsr    input
  1175.     beq    outstrg1    ; jump if no input
  1176.     cmpa    #ctlw
  1177.     bne    outstrg1    ; jump if not cntlw
  1178. outstrg2:
  1179.     jsr    input
  1180.     beq    outstrg2    ; jump if any input
  1181.     bra    outstrg1
  1182. outstrg3:
  1183.     pula
  1184.     rts
  1185.  
  1186. ;**********
  1187. ;*    inchar() - reads input until character sent.
  1188. ;*    echoes char and returns with a = char.
  1189. inchar:    jsr    input
  1190.     tsta
  1191.     beq    inchar        ; jump if no input
  1192.     jsr    output        ; echo
  1193.     rts
  1194.  
  1195. ;*********************
  1196. ;*** command table ***
  1197. comtabl    = .
  1198.     .byte    5
  1199.     .ascii    'ASSEM'
  1200.     .word    #assem
  1201.     .byte    5
  1202.     .ascii    'BREAK'
  1203.     .word    #break
  1204.     .byte    4
  1205.     .ascii    'BULK'
  1206.     .word    #bulk
  1207.     .byte    7
  1208.     .ascii    'BULKALL'
  1209.     .word    #bulkall
  1210.     .byte    4
  1211.     .ascii    'CALL'
  1212.     .word    #call
  1213.     .byte    4
  1214.     .ascii    'DUMP'
  1215.     .word    #dump
  1216.     .byte    4
  1217.     .ascii    'FILL'
  1218.     .word    #fill
  1219.     .byte    2
  1220.     .ascii    'GO'
  1221.     .word    #go
  1222.     .byte    4
  1223.     .ascii    'HELP'
  1224.     .word    #help
  1225.     .byte    4
  1226.     .ascii    'HOST'
  1227.     .word    #host
  1228.     .byte    4
  1229.     .ascii    'LOAD'
  1230.     .word    #load
  1231.     .byte    6         ; length of command
  1232.     .ascii    'MEMORY'    ; ascii command
  1233.     .word    #memory        ; command address
  1234.     .byte    4
  1235.     .ascii    'MOVE'
  1236.     .word    #move
  1237.     .byte    7
  1238.     .ascii    'PROCEED'
  1239.     .word    #proceed
  1240.     .byte    8
  1241.     .ascii    'REGISTER'
  1242.     .word    #register
  1243.     .byte    5
  1244.     .ascii    'TRACE'
  1245.     .word    #trace
  1246.     .byte    6
  1247.     .ascii    'VERIFY'
  1248.     .word    #verify
  1249.     .byte    1
  1250.     .ascii    '?'        ; initial command
  1251.     .word    #help
  1252.     .byte    5
  1253.     .ascii    'XBOOT'
  1254.     .word    #boot
  1255. ;*
  1256. ;*** command names for evm compatability ***
  1257. ;*
  1258.     .byte    3
  1259.     .ascii    'ASM'
  1260.     .word    #assem
  1261.     .byte    2
  1262.     .ascii    'BF'
  1263.     .word    #fill
  1264.     .byte    4
  1265.     .ascii    'COPY'
  1266.     .word    #move
  1267.     .byte    5
  1268.     .ascii    'ERASE'
  1269.     .word    #bulk
  1270.     .byte    2
  1271.     .ascii    'MD'
  1272.     .word    #dump
  1273.     .byte    2
  1274.     .ascii    'MM'
  1275.     .word    #memory
  1276.     .byte    2
  1277.     .ascii    'RD'
  1278.     .word    #register
  1279.     .byte    2
  1280.     .ascii    'RM'
  1281.     .word    #register
  1282.     .byte    4
  1283.     .ascii    'READ'
  1284.     .word    #move
  1285.     .byte    2
  1286.     .ascii    'TM'
  1287.     .word    #host
  1288.     .byte    4
  1289.     .ascii    'TEST'
  1290.     .word    #evbtest
  1291.     .byte    -1
  1292.  
  1293. ;*******************
  1294. ;*** text tables ***
  1295.  
  1296. msg1:    .ascii    'BUFFALO 2.5 (ext) - '
  1297.     .ascii    'Bit User Fast Friendly Aid to Logical Operation'
  1298.     .byte    eot
  1299. msg2:    .ascii    'What?'
  1300.     .byte    eot
  1301. msg3:    .ascii    'Too Long'
  1302.     .byte    eot
  1303. msg4:    .ascii    'Full'
  1304.     .byte    eot
  1305. msg5:    .ascii    'Op- '
  1306.     .byte    eot
  1307. msg6:    .ascii    'rom-'
  1308.     .byte    eot
  1309. msg8:    .ascii    'Command?'
  1310.     .byte    eot
  1311. msg9:    .ascii    'Bad argument'
  1312.     .byte    eot
  1313. msg10:    .ascii    'No host port available'
  1314.     .byte    eot
  1315. msg11:    .ascii    'done'
  1316.     .byte    eot
  1317. msg12:    .ascii    'checksum error'
  1318.     .byte    eot
  1319. msg13:    .ascii    'error addr '
  1320.     .byte    eot
  1321.  
  1322. ;**********
  1323. ;*    break [-][<addr>] . . .
  1324. ;* modifies the breakpoint table.  more than
  1325. ;* one argument can be entered on the command
  1326. ;* line but the table will hold only 4 entries.
  1327. ;* 4 types of arguments are implied above:
  1328. ;* break         prints table contents.
  1329. ;* break <addr>        inserts <addr>.
  1330. ;* break -<addr>    deletes <addr>.
  1331. ;* break -        clears all entries.
  1332. ;**********
  1333. ;* while 1
  1334. ;*    a = wskip();
  1335. ;*    switch(a)
  1336. ;*        case(cr):
  1337. ;*        bprint(); return;
  1338.  
  1339. break:    jsr    wskip
  1340.     cmpa    #0x0d
  1341.     bne    brkdel        ; jump if not cr
  1342.     jsr    bprint        ; print table
  1343.     rts
  1344.  
  1345. ;*        case("-"):
  1346. ;*        incbuff(); readbuff();
  1347. ;*        if(dchek(a))        /* look for wspac or cr */
  1348. ;*            bpclr();
  1349. ;*            breaksw;
  1350. ;*        a = buffarg();
  1351. ;*        if( !dchek(a) ) return(bad argument);
  1352. ;*        b = bpsrch();
  1353. ;*        if(b >= 0)
  1354. ;*            brktabl[b] = 0;
  1355. ;*        breaksw;
  1356.  
  1357. brkdel:    cmpa    #'-
  1358.     bne    brkdef        ; jump if not -
  1359.     jsr    incbuff
  1360.     jsr    readbuff
  1361.     jsr    dchek
  1362.     bne    brkdel1        ; jump if not delimeter
  1363.     jsr    bpclr        ; clear table
  1364.     jmp    break        ; do next argument
  1365. brkdel1:
  1366.     jsr    buffarg        ; get address to delete
  1367.     jsr    dchek
  1368.     beq    brkdel2        ; jump if delimeter
  1369.     ldx    #msg9        ; "bad argument"
  1370.     jsr    outstrg
  1371.     rts
  1372. brkdel2:
  1373.     jsr    bpsrch        ; look for addr in table
  1374.     tstb
  1375.     bmi    brkdel3        ; jump if not found
  1376.     ldx    #brktabl
  1377.     abx
  1378.     clr    0,x        ; clear entry
  1379.     clr    1,x
  1380. brkdel3:
  1381.     jmp    break        ; do next argument
  1382.  
  1383. ;*        default:
  1384. ;*        a = buffarg();
  1385. ;*        if( !dchek(a) ) return(bad argument);
  1386. ;*        b = bpsrch();
  1387. ;*        if(b < 0)        /* not already in table */
  1388. ;*            x = shftreg;
  1389. ;*            shftreg = 0;
  1390. ;*            a = x[0]; x[0] = 0x3f
  1391. ;*            b = x[0]; x[0] = a;
  1392. ;*            if(b != 0x3f) return(rom);
  1393. ;*            b = bpsrch();    /* look for hole */
  1394. ;*            if(b >= 0) return(table full);
  1395. ;*            brktabl[b] = x;
  1396. ;*        breaksw;
  1397.  
  1398. brkdef:    jsr    buffarg        ; get argument
  1399.     jsr    dchek
  1400.     beq    brkdef1        ; jump if delimiter
  1401.     ldx    #msg9        ; "bad argument"
  1402.     jsr    outstrg
  1403.     rts
  1404. brkdef1:
  1405.     jsr    bpsrch        ; look for entry in table
  1406.     tstb
  1407.     bge    break        ; jump if already in table
  1408.     ldx    *shftreg    ; x = new entry
  1409.     ldaa    0,x
  1410.     ldab    #swi
  1411.     stab    0,x
  1412.     ldab    0,x
  1413.     staa    0,x
  1414.     cmpb    #swi
  1415.     beq    brkdef2        ; jump if writes ok
  1416.     stx    *ptr1        ; save address
  1417.     ldx    #msg6        ; "rom-"
  1418.     jsr    outstrg
  1419.     ldx    #ptr1
  1420.     jsr    out2bsp        ; print address
  1421.     jsr    bprint
  1422.     rts
  1423. brkdef2:
  1424.     clr    *shftreg
  1425.     clr    *shftreg+1
  1426.     pshx
  1427.     jsr    bpsrch        ; look for 0 entry
  1428.     pulx
  1429.     tstb
  1430.     bpl    brkdef3        ; jump if table not full
  1431.     ldx    #msg4        ; "full"
  1432.     jsr    outstrg
  1433.     jsr    bprint
  1434.     rts
  1435. brkdef3:
  1436.  
  1437.     ldy    #brktabl
  1438.     aby
  1439.     stx    0,y        ; put new entry in
  1440.     jmp    break        ; do next argument
  1441.  
  1442. ;**********
  1443. ;*    bprint() - print the contents of the table.
  1444. ;**********
  1445. bprint:    jsr    outcrlf
  1446.     ldx    #brktabl
  1447.     ldab    #4
  1448. bprint1:
  1449.     jsr    out2bsp
  1450.     decb
  1451.     bgt    bprint1        ; loop 4 times
  1452.     rts
  1453.  
  1454. ;**********
  1455. ;*    bpsrch() - search table for address in
  1456. ;* shftreg. returns b = index to entry or
  1457. ;* b = -1 if not found.
  1458. ;**********
  1459. ;*for(b=0; b=6; b=+2)
  1460. ;*    x[] = brktabl + b;
  1461. ;*    if(x[0] = shftreg)
  1462. ;*        return(b);
  1463. ;*return(-1);
  1464.  
  1465. bpsrch:    clrb
  1466. bpsrch1:
  1467.     ldx    #brktabl
  1468.     abx
  1469.     ldx    0,x        ; get table entry
  1470.     cpx    *shftreg
  1471.     bne    bpsrch2        ; jump if no match
  1472.     rts
  1473. bpsrch2:
  1474.     incb
  1475.     incb
  1476.     cmpb    #0x6
  1477.     ble    bpsrch1        ; loop 4 times
  1478.     ldab    #0xff
  1479.     rts
  1480.  
  1481.  
  1482. ;**********
  1483. ;*    bulk - bulk erase the eeprom except the
  1484. ;* config register.
  1485. ;**********
  1486. bulk:
  1487.     clr    *tmp2
  1488.     bra    bulk1
  1489.  
  1490. ;**********
  1491. ;*    bulkall - bulk erase the eeprom and the
  1492. ;* config register.
  1493. ;**********
  1494. bulkall:
  1495.     clr    *tmp2
  1496.     inc    *tmp2
  1497.  
  1498. ;*set up pprog register for erase
  1499. bulk1:    psha
  1500.     ldaa    #0x06
  1501.     staa    pprog        ; set eelat, erase bits
  1502.  
  1503. ;*if (ee only) write to 0xb600
  1504. ;*else write to config register
  1505.     ldaa    #0xff
  1506.     tst    *tmp2
  1507.     bne    bulk2        ; jump if config
  1508.     staa    0xb600        ; write to 0xb600
  1509.     bra    bulk3
  1510. bulk2:    staa    config
  1511. bulk3    = .
  1512.  
  1513. ;*start erasing
  1514.     ldaa    #0x07
  1515.     bne    acl3
  1516.     clra            ; fail safe
  1517. acl3:    staa    pprog
  1518.  
  1519. ;*delay for 10 ms at E = 2 mhz
  1520.     pshx
  1521.     ldx    #0x0d06        ; 6~ * 3334 = 20,004 * 0.5 mhz
  1522. bulkdly:
  1523.     dex            ; 2~
  1524.     bne    bulkdly        ; 3~
  1525.     pulx
  1526.  
  1527. ;*stop programming
  1528.     clr    pprog
  1529.     pula
  1530.     rts
  1531.  
  1532. ;**********
  1533. ;*    dump [<addr1> [<addr2>]]  - dump memory
  1534. ;* in 16 byte lines from <addr1> to <addr2>.
  1535. ;*    default starting address is "current
  1536. ;* location" and default number of lines is 8.
  1537. ;**********
  1538. ;*ptr1 = ptrmem;    /* default start address */
  1539. ;*ptr2 = ptr1 + 0x80;    /* default end address */
  1540. ;*a = wskip();
  1541. ;*if(a != cr)
  1542. ;*    a = buffarg();
  1543. ;*    if(countu1 = 0) return(bad argument);
  1544. ;*    if( !dchek(a) ) return(bad argument);
  1545. ;*    ptr1 = shftreg;
  1546. ;*    ptr2 = ptr1 + 0x80;    /* default end address */
  1547. ;*    a = wskip();
  1548. ;*    if(a != cr)
  1549. ;*        a = buffarg();
  1550. ;*        if(countu1 = 0) return(bad argument);
  1551. ;*        a = wskip();
  1552. ;*        if(a != cr) return(bad argument);
  1553. ;*        ptr2 = shftreg;
  1554.  
  1555. dump:    ldx    *ptrmem        ; current location
  1556.     stx    *ptr1        ; default start
  1557.     ldab    #0x80
  1558.     abx
  1559.     stx    *ptr2        ; default end
  1560.     jsr    wskip
  1561.     cmpa    #0xd
  1562.     beq    dump1        ; jump - no arguments
  1563.     jsr    buffarg        ; read argument
  1564.     tst    *count
  1565.     beq    dumperr        ; jump if no argument
  1566.     jsr    dchek
  1567.     bne    dumperr        ; jump if delimiter
  1568.     ldx    *shftreg
  1569.     stx    *ptr1
  1570.     ldab    #0x80
  1571.     abx
  1572.     stx    *ptr2        ; default end address
  1573.     jsr    wskip
  1574.     cmpa    #0xd
  1575.     beq    dump1        ; jump - 1 argument
  1576.     jsr    buffarg        ; read argument
  1577.     tst    *count
  1578.     beq    dumperr        ; jump if no argument
  1579.     jsr    wskip
  1580.     cmpa    #0x0d
  1581.     bne    dumperr        ; jump if not cr
  1582.     ldx    *shftreg
  1583.     stx    *ptr2
  1584.     bra    dump1        ; jump - 2 arguments
  1585. dumperr:
  1586.     ldx    #msg9        ; "bad argument"
  1587.     jsr    outstrg
  1588.     rts
  1589.  
  1590. ;*ptrmem = ptr1;
  1591. ;*ptr1 = ptr1 & 0xfff0;
  1592.  
  1593. dump1:    ldd    *ptr1
  1594.     std    *ptrmem        ; new current location
  1595.     andb    #0xf0
  1596.     std    *ptr1        ; start dump at 16 byte boundary
  1597.  
  1598. ;*** dump loop starts here ***
  1599. ;*do:
  1600. ;*    output address of first byte;
  1601.  
  1602. dumplp:    jsr    outcrlf
  1603.     ldx    #ptr1
  1604.     jsr    out2bsp        ; first address
  1605.  
  1606. ;*    x = ptr1;
  1607. ;*    for(b=0; b=16; b++)
  1608. ;*        output contents;
  1609.  
  1610.     ldx    *ptr1        ; base address
  1611.     clrb            ; loop counter
  1612. dumpdat:
  1613.     jsr    out1bsp        ; hex value loop
  1614.     incb
  1615.     cmpb    #0x10
  1616.     blt    dumpdat        ; loop 16 times
  1617.  
  1618. ;*    x = ptr1;
  1619. ;*    for(b=0; b=16; b++)
  1620. ;*        a = x[b];
  1621. ;*        if(0x7a < a < 0x20)  a = 0x20;
  1622. ;*        output ascii contents;
  1623.  
  1624.     clrb            ; loop counter
  1625. dumpasc:
  1626.     ldx    *ptr1        ; base address
  1627.     abx
  1628.     ldaa    ,x        ; ascii value loop
  1629.     cmpa    #0x20
  1630.     blo    dump3        ; jump if non printable
  1631.     cmpa    #0x7a
  1632.     bls    dump4        ; jump if printable
  1633. dump3:    ldaa    #0x20        ; space for non printables
  1634. dump4:    jsr    output        ; output ascii value
  1635.     incb
  1636.     cmpb    #0x10
  1637.     blt    dumpasc        ; loop 16 times
  1638.  
  1639. ;*    chkabrt();
  1640. ;*    ptr1 = ptr1 + 0x10;
  1641. ;*while(ptr1 <= ptr2);
  1642. ;*return;
  1643.  
  1644.     jsr    chkabrt        ; check abort or wait
  1645.     ldd    *ptr1
  1646.     addd    #0x10        ; point to next 16 byte bound
  1647.     std    *ptr1        ; update ptr1
  1648.     cpd    *ptr2
  1649.     bhi    dump5        ; quit if ptr1 > ptr2
  1650.     cpd    #0x00        ; check wraparound at 0xffff
  1651.     bne    dumplp        ; jump - no wraparound
  1652.     ldd    *ptr2
  1653.     cpd    #0xfff0
  1654.     blo    dumplp        ; upper bound not at top
  1655. dump5:    rts            ; quit
  1656.  
  1657. ;**********
  1658. ;*    fill <addr1> <addr2> [<data>]  - block fill
  1659. ;*memory from addr1 to addr2 with data.    data
  1660. ;*defaults to 0xff.
  1661. ;**********
  1662. ;*get addr1 and addr2
  1663.  
  1664. fill    = .
  1665.     jsr    wskip
  1666.     jsr    buffarg
  1667.     tst    *count
  1668.     beq    fillerr        ; jump if no argument
  1669.     jsr    wchek
  1670.     bne    fillerr        ; jump if bad argument
  1671.     ldx    *shftreg
  1672.     stx    *ptr1        ; address1
  1673.     jsr    wskip
  1674.     jsr    buffarg
  1675.     tst    *count
  1676.     beq    fillerr        ; jump if no argument
  1677.     jsr    dchek
  1678.     bne    fillerr        ; jump if bad argument
  1679.     ldx    *shftreg
  1680.     stx    *ptr2        ; address2
  1681.  
  1682. ;*get data if it exists
  1683.     ldaa    #0xff
  1684.     staa    *tmp2        ; default data
  1685.     jsr    wskip
  1686.     cmpa    #0x0d
  1687.     beq    fill1        ; jump if default data
  1688.     jsr    buffarg
  1689.     tst    *count
  1690.     beq    fillerr        ; jump if no argument
  1691.     jsr    wskip
  1692.     cmpa    #0x0d
  1693.     bne    fillerr        ; jump if bad argument
  1694.     ldaa    *shftreg+1
  1695.     staa    *tmp2
  1696.  
  1697. ;*while(ptr1 <= ptr2)
  1698. ;*    *ptr1 = data
  1699. ;*    if(*ptr1 != data) abort
  1700.  
  1701. fill1    = .
  1702.     jsr    chkabrt        ; check for abort
  1703.     ldx    *ptr1        ; starting address
  1704.     ldaa    *tmp2        ; data
  1705.     staa    0,x
  1706.     cmpa    0,x
  1707.     bne    fillbad        ; jump if no write
  1708.     cpx    *ptr2
  1709.     beq    fill2        ; quit yet?
  1710.     inx
  1711.     stx    *ptr1
  1712.     bra    fill1        ; loop
  1713. fill2:    rts
  1714.  
  1715. fillerr:
  1716.     ldx    #msg9        ; "bad argument"
  1717.     jsr    outstrg
  1718.     rts
  1719.  
  1720. fillbad:
  1721.     ldx    #msg6        ; "rom -"
  1722.     jsr    outstrg
  1723.     ldx    #ptr1
  1724.     jsr    out2bsp
  1725.     rts
  1726.  
  1727. ;**********
  1728. ;*    call [<addr>] - execute a jsr to addr or
  1729. ;*user's pc value.  return to monitor by rts
  1730. ;*or breakpoint.
  1731. ;**********
  1732. ;*a = wskip();
  1733. ;*if(a != cr)
  1734. ;*    a = buffarg();
  1735. ;*    a = wskip();
  1736. ;*    if(a != cr) return(bad argument)
  1737. ;*    pc = shftreg;
  1738.  
  1739. call:    jsr    wskip
  1740.     cmpa    #0xd
  1741.     beq    call3        ; jump if no arg
  1742.     jsr    buffarg
  1743.     jsr    wskip
  1744.     cmpa    #0xd
  1745.     beq    call2        ; jump if cr
  1746.     ldx    #msg9        ; "bad argument"
  1747.     jsr    outstrg
  1748.     rts
  1749. call2:    ldx    *shftreg
  1750.     stx    *regs        ; pc = <addr>
  1751.  
  1752. ;*user_stack[0] = return_to_monitor;
  1753. ;*setbps();
  1754. ;*restack();    /* restack and go*/
  1755.  
  1756. call3:    ldx    *sp
  1757.     dex            ; user stack pointer
  1758.     ldd    #return        ; return address
  1759.     std    0,x
  1760.     dex
  1761.     stx    *sp        ; new user stack pointer
  1762.     jsr    setbps
  1763.     clr    *tmp2        ; flag for breakpoints
  1764.     jmp    restack        ; executes an rti
  1765.  
  1766. ;**********
  1767. ;*    return() - return here from rts after
  1768. ;*call command.
  1769. ;**********
  1770. return:    psha            ; save a register
  1771.     tpa
  1772.     staa    *regs+8        ; cc register
  1773.     pula
  1774.     std    *regs+6        ; a and b registers
  1775.     stx    *regs+4        ; x register
  1776.     sty    *regs+2        ; y register
  1777.     sts    *sp        ; user stack pointer
  1778.     lds    #stack        ; monitor stack pointer
  1779.     jsr    rembps        ; remove breakpoints
  1780.     jsr    outcrlf
  1781.     jsr    rprint        ; print user registers
  1782.     jmp    main
  1783.  
  1784. ;**********
  1785. ;*    go [<addr>] - execute starting at <addr> or
  1786. ;*user's pc value.  executes an rti to user code.
  1787. ;*returns to monitor via an swi through swiin.
  1788. ;**********
  1789. ;*a = wskip();
  1790. ;*if(a != cr)
  1791. ;*    a = buffarg();
  1792. ;*    a = wskip();
  1793. ;*    if(a != cr) return(bad argument)
  1794. ;*    pc = shftreg;
  1795. ;*setbps();
  1796. ;*restack();    /* restack and go*/
  1797.  
  1798. go:    jsr    wskip
  1799.     cmpa    #0x0d
  1800.     beq    go2        ; jump if no arg
  1801.     jsr    buffarg
  1802.     jsr    wskip
  1803.     cmpa    #0x0d
  1804.     beq    go1        ; jump if cr
  1805.     ldx    #msg9        ; "bad argument"
  1806.     jsr    outstrg
  1807.     rts
  1808. go1:    ldx    *shftreg
  1809.     stx    *regs        ; pc = <addr>
  1810. go2:    clr    *tmp2        ; flag for breakpoints
  1811.     inc    *tmp2        ; (1=go, 0=call)
  1812.     jsr    setbps
  1813.     jmp    restack        ; execute an rti
  1814.  
  1815. ;**********
  1816. ;*    swiin() - return from swi.    set up
  1817. ;*stack pointers, save user registers, and
  1818. ;*return to main.
  1819. ;**********
  1820. swiin:    tsx            ; swi entry point
  1821.     lds    #stack
  1822.     jsr    savstack    ; save user regs
  1823.     ldx    *regs
  1824.     dex
  1825.     stx    *regs        ; save user pc
  1826.     ldx    *ptr4        ; restore user swi vector
  1827.     stx    *jswi+1
  1828.  
  1829. ;*if(flagt1 = 0) remove return addr from stack;
  1830.  
  1831.     tst    *tmp2        ; 0=call, 1=go
  1832.     bne    go3        ; jump if go command
  1833.     ldx    *sp        ; remove return address
  1834.     inx
  1835.     inx
  1836.     stx    *sp
  1837. go3:    jsr    outcrlf        ; print register values
  1838.     jsr    rprint
  1839.     jsr    rembps
  1840.     jmp    main        ; return to monitor
  1841. ;*                ; (sp destroyed above)
  1842.  
  1843. ;**********
  1844. ;*    proceed - same as go except it ignores
  1845. ;*a breakpoint at the first opcode.  calls
  1846. ;*trace once and the go.
  1847. ;**********
  1848. proceed:
  1849.     clr    *tmp2        ; flag for breakpoints
  1850.     inc    *tmp2        ; 0=trace, 1=proceed
  1851.     jmp    trace3
  1852.  
  1853. ;**********
  1854. ;*    trace <n> - trace n instructions starting
  1855. ;*at user's pc value. n is a hex number less than
  1856. ;*0xff (defaults to 1).
  1857. ;**********
  1858. ;*countt1 = 1
  1859. ;*a = wskip();
  1860. ;*if(a != cr)
  1861. ;*    a = buffarg(); a = wskip();
  1862. ;*    if(a != cr) return(bad argument);
  1863. ;*    countt1 = n
  1864.  
  1865. trace:    clr    *tmp4
  1866.     inc    *tmp4        ; default countt1 = 1
  1867.     clr    *tmp2        ; 0 = trace
  1868.     jsr    wskip
  1869.     cmpa    #0x0d
  1870.     beq    trace2        ; jump if cr
  1871.     jsr    buffarg
  1872.     jsr    wskip
  1873.     cmpa    #0x0d
  1874.     beq    trace1        ; jump if cr
  1875.     ldx    #msg9        ; "bad argument"
  1876.     jsr    outstrg
  1877.     rts
  1878. trace1:    ldaa    *shftreg+1    ; n
  1879.     staa    *tmp4
  1880.  
  1881. ;*print opcode
  1882. trace2:    jsr    outcrlf
  1883.     ldx    #msg5        ; "op-"
  1884.     jsr    outstrg
  1885.     ldx    *regs
  1886.     jsr    out1bsp        ; opcode
  1887.  
  1888. ;*save user oc5 regs, setup monitor oc5 regs
  1889. trace3:    ldaa    tctl1
  1890.     staa    *ptr2        ; save user mode/level
  1891.     anda    #0xfc
  1892.     staa    tctl1        ; disable oc5 output
  1893.     ldaa    tmsk1
  1894.     staa    *ptr2+1        ; save user int masks
  1895.     clr    tmsk2        ; disable tof and pac ints
  1896.  
  1897. ;*put monitor toc5 vector into jump table
  1898.     ldx    *jtoc5+1
  1899.     stx    *ptr4        ; save user's vector
  1900.     ldaa    #0x7e        ; jmp opcode
  1901.     staa    *jtoc5
  1902.     ldx    #tracein
  1903.     stx    *jtoc5+1    ; monitor toc5 vector
  1904.  
  1905. ;*unmask i bit in user ccr
  1906.     ldaa    *regs+8        ; user ccr
  1907.     anda    #0xef        ; clear i bit
  1908.     staa    *regs+8
  1909.  
  1910. ;*arm oc5 interrupt
  1911.     ldab    #87        ; cycles to end of rti
  1912.     ldx    tcnt        ; timer count value
  1913.     abx            ;             3~ )
  1914.     stx    toc5        ; oc5 match register    5~  )
  1915.     ldaa    #0x08        ;             2~    )
  1916.     staa    tflg1        ; clear oc5 int flag    4~    ) 86~
  1917.     staa    tmsk1        ; enable oc5 interrupt    4~    )
  1918.     cli            ;             2~  )
  1919.     jmp    restack        ; execute an rti     66~ )
  1920.  
  1921. ;**********
  1922. ;*    tracein - return from toc5 interrupt.
  1923. ;**********
  1924. ;*disable toc5 interrupt
  1925. ;*replace user's toc5 vector
  1926. tracein:
  1927.     sei
  1928.     clr    tmsk1        ; disable timer ints
  1929.     tsx
  1930.     lds    #stack
  1931.     jsr    savstack    ; save user regs
  1932.     ldx    *ptr4
  1933.     stx    *jtoc5+1
  1934.     jsr    chkabrt        ; check for abort
  1935.  
  1936. ;*if(flagt1 = 1) jump to go command ( proceed )
  1937.     tst    *tmp2
  1938.     beq    trace9        ; jump if trace command
  1939.     jmp    go2
  1940.  
  1941. ;*rprint();
  1942. ;*while(countt1 >= 0) continue trace;
  1943.  
  1944. trace9:    jsr    outcrlf        ; print registers for
  1945.     jsr    rprint        ; trace only.
  1946.     dec    *tmp4
  1947.     bhi    trace2        ; jump if countt1 >= 0
  1948.     jmp    main        ; return to monitor
  1949. ;*                ; (sp destroyed above)
  1950.  
  1951. ;**********
  1952. ;*    setbps - replace user code with swi's at
  1953. ;*breakpoint addresses.
  1954. ;**********
  1955. ;*for(b=0; b=6; b =+ 2)
  1956. ;*    x = brktabl[b];
  1957. ;*    if(x != 0)
  1958. ;*        optabl[b] = x[0];
  1959. ;*        x[0] = 0x3f;
  1960.  
  1961. setbps:    clrb
  1962. setbps1:
  1963.     ldx    #brktabl
  1964.     ldy    #ptr6
  1965.     abx
  1966.     aby
  1967.     ldx    0,x        ; breakpoint table entry
  1968.     beq    setbps2        ; jump if 0
  1969.     ldaa    0,x        ; save user opcode
  1970.     staa    0,y
  1971.     ldaa    #swi        ; insert swi into code
  1972.     staa    0,x
  1973. setbps2:
  1974.     addb    #0x2
  1975.     cmpb    #0x6
  1976.     ble    setbps1        ; loop 4 times
  1977.  
  1978. ;*put monitor swi vector into jump table
  1979.     ldx    *jswi+1
  1980.     stx    *ptr4        ; save user swi vector
  1981.     ldaa    #0x7e        ; jmp opcode
  1982.     staa    *jswi
  1983.     ldx    #swiin
  1984.     stx    *jswi+1        ; monitor swi vector
  1985.     rts
  1986.  
  1987. ;**********
  1988. ;*    rembps - remove breakpoints from user code.
  1989. ;**********
  1990. ;*for(b=0; b=6; b =+ 2)
  1991. ;*    x = brktabl[b];
  1992. ;*    if(x != 0)
  1993. ;*        x[0] = optabl[b];
  1994.  
  1995. rembps:    clrb
  1996. rembps1:
  1997.     ldx    #brktabl
  1998.     ldy    #ptr6
  1999.     abx
  2000.     aby
  2001.     ldx    0,x        ; breakpoint table entry
  2002.     beq    rembps2        ; jump if 0
  2003.     ldaa    0,y        ; restore user's opcode
  2004.     staa    0,x
  2005. rembps2:
  2006.     addb    #0x2
  2007.     cmpb    #0x6
  2008.     ble    rembps1        ; loop 4 times
  2009.  
  2010. ;*replace user's swi vector
  2011.     ldx    *ptr4
  2012.     stx    *jswi+1
  2013.     rts
  2014.  
  2015. ;**********
  2016. ;*    restack() - restore user stack and
  2017. ;*execute an rti. extended addressing forced
  2018. ;*to ensure count value for trace.
  2019. ;**********
  2020. restack:
  2021.     lds    sp        ; stack pointer
  2022.     ldx    regs
  2023.     pshx            ; pc
  2024.     ldx    regs+2
  2025.     pshx            ; y
  2026.     ldx    regs+4
  2027.     pshx            ; x
  2028.     ldd    regs+6
  2029.     psha            ; a
  2030.     pshb            ; b
  2031.     ldaa    regs+8
  2032.     psha            ; ccr
  2033. restack1:
  2034.     rti
  2035.  
  2036. ;**********
  2037. ;*    savstack() -    save user's registers.
  2038. ;**********
  2039. savstack:
  2040.     ldaa    0,x
  2041.     staa    *regs+8        ; ccr
  2042.     ldd    1,x
  2043.     staa    *regs+7        ; b
  2044.     stab    *regs+6        ; a
  2045.     ldd    3,x
  2046.     std    *regs+4        ; x
  2047.     ldd    5,x
  2048.     std    *regs+2        ; y
  2049.     ldd    7,x
  2050.     std    *regs        ; pc
  2051.     ldab    #8
  2052.     abx
  2053.     stx    *sp        ; stack pointer
  2054.     rts
  2055.  
  2056. ;**********
  2057. ;*    help  -  list buffalo commands to terminal.
  2058. ;**********
  2059. help    = .
  2060.     ldx    #helpmsg1
  2061.     jsr    outstrg        ; print help screen
  2062.     rts
  2063.  
  2064. helpmsg1    = .
  2065.     .ascii    'ASM [<addr>]  Line assembler/disassembler.'
  2066.     .byte    0x0d
  2067.     .ascii    '    /        Do same address.'
  2068.     .ascii    '           ^        Do previous address.'
  2069.     .byte    0x0d
  2070.     .ascii    '    CTRL-J   Do next address.'
  2071.     .ascii    '           RETURN   Do next opcode.'
  2072.     .byte    0x0d
  2073.     .ascii    '    CTRL-A   Quit.'
  2074.     .byte    0x0d
  2075.     .ascii    'BF <addr1> <addr2> [<data>]  Block fill.'
  2076.     .byte    0x0d
  2077.     .ascii    'BR [-][<addr>]  Set up breakpoint table.'
  2078.     .byte    0x0d
  2079.     .ascii    'BULK  Erase the EEPROM.'
  2080.     .ascii    '                   BULKALL  Erase EEPROM and CONFIG.'
  2081.     .byte    0x0d
  2082.     .ascii    'CALL [<addr>]  Call user subroutine.'
  2083.     .ascii    '      G [<addr>]  Execute user code.'
  2084.     .byte    0x0d
  2085.     .ascii    'LOAD, VERIFY [T] <host download command>'
  2086.     .ascii    '  Load or verify S-records.'
  2087.     .byte    0x0d
  2088.     .ascii    'MD [<addr1> [<addr2>]]  Memory dump.'
  2089.     .byte    0x0d
  2090.     .ascii    'MM [<addr>]  Memory modify.'
  2091.     .byte    0x0d
  2092.     .ascii    '    /        Open same address.         CTRL-H'
  2093.     .ascii    ' or ^   Open previous address.'
  2094.     .byte    0x0d
  2095.     .ascii    '    CTRL-J   Open next address.         SPACE'
  2096.     .ascii    '         Open next address.'
  2097.     .byte    0x0d
  2098.     .ascii    '    RETURN   Quit.                      <addr>O'
  2099.     .ascii    '       Compute offset to <addr>.'
  2100.     .byte    0x0d
  2101.     .ascii    'MOVE <s1> <s2> [<d>]  Block move.'
  2102.     .byte    0x0d
  2103.     .ascii    'P  Proceed/continue execution.'
  2104.     .byte    0x0d
  2105.     .ascii    'RM [P, Y, X, A, B, C, or S]  Register modify.'
  2106.     .byte    0x0d
  2107.     .ascii    'T [<n>]  Trace n instructions.'
  2108.     .byte    0x0d
  2109.     .ascii    'TM  Transparent mode (CTRL-A = exit, CTRL-B = send break).'
  2110.     .byte    0x0d
  2111.     .ascii    'CTRL-H  Backspace.'
  2112.     .ascii    '                      CTRL-W  Wait for any key.'
  2113.     .byte    0x0d
  2114.     .ascii    'CTRL-X or DELETE  Abort/cancel command.'
  2115.     .byte    0x0d
  2116.     .ascii    'RETURN  Repeat last command.'
  2117.     .byte    4
  2118.  
  2119. ;**********
  2120. ;*    host() - establishes transparent link between
  2121. ;*    terminal and host.  port used for host is
  2122. ;*    determined in the reset initialization routine
  2123. ;*    and stored in hostdev.
  2124. ;*        to exit type control a.
  2125. ;*        to send break to host type control b.
  2126. ;*if(no external device) return;
  2127. ;*initialize host port;
  2128. ;*while( !(control a))
  2129. ;*    input(terminal); output(host);
  2130. ;*    input(host); output(terminal);
  2131.  
  2132. host:    ldaa    *extdev
  2133.     bne    host0        ; jump if host port avail.
  2134.     ldx    #msg10        ; "no host port avail"
  2135.     jsr    outstrg
  2136.     rts
  2137. host0:    clr    *autolf        ; turn off autolf
  2138.     jsr    hostco        ; connect sci (evb board)
  2139.     jsr    hostinit    ; initialize host port
  2140. host1:    jsr    input        ; read terminal
  2141.     tsta
  2142.     beq    host3        ; jump if no char
  2143.     cmpa    #ctla
  2144.     beq    hostend        ; jump if control a
  2145.     cmpa    #ctlb
  2146.     bne    host2        ; jump if not control b
  2147.     jsr    txbreak        ; send break to host
  2148.     bra    host3
  2149. host2:    jsr    hostout        ; echo to host
  2150. host3:    jsr    hostin        ; read host
  2151.     tsta
  2152.     beq    host1        ; jump if no char
  2153.     jsr    output        ; echo to terminal
  2154.     bra    host1
  2155. hostend:
  2156.     inc    *autolf        ; turn on autolf
  2157.     jsr    targco        ; disconnect sci (evb board)
  2158.     rts            ; return
  2159.  
  2160. ;**********
  2161. ;* txbreak() - transmit break to host port.
  2162. ;* the duration of the transmitted break is
  2163. ;* approximately 200,000 e-clock cycles, or
  2164. ;* 100ms at 2.0 mhz.
  2165. ;***********
  2166. txbreak    = .
  2167.     ldaa    *hostdev
  2168.     cmpa    #0x03
  2169.     beq    txbdu        ; jump if duartb is host
  2170.  
  2171. txbsci:    ldx    #sccr2        ; sci is host
  2172.     bset    0,x ,#0x01    ; set send break bit
  2173.     bsr    txbwait
  2174.     bclr    0,x ,#0x01    ; clear send break bit
  2175.     bra txb1
  2176.  
  2177. txbdu:    ldx    #portb        ; duart host port
  2178.     ldaa    #0x60        ; start break cmd
  2179.     staa    2,x        ; port b command register
  2180.     bsr    txbwait
  2181.     ldaa    #0x70        ; stop break cmd
  2182.     staa    2,x        ; port b command register
  2183.  
  2184. txb1:    ldaa    #0x0d
  2185.     jsr    hostout        ; send carriage return
  2186.     ldaa    #0x0a
  2187.     jsr    hostout        ; send linefeed
  2188.     rts
  2189.  
  2190. txbwait:
  2191.     ldy    #0x6f9b        ; loop count = 28571
  2192. txbwait1:
  2193.     dey            ; 7 cycle loop
  2194.     bne    txbwait1
  2195.     rts
  2196.  
  2197.  
  2198. ;**********
  2199. ;*    hostinit(), hostin(), hostout() - host i/o
  2200. ;*routines.  restores original terminal device.
  2201. ;**********
  2202. hostinit:
  2203.     ldab    *iodev        ; save terminal
  2204.     pshb
  2205.     ldab    *hostdev
  2206.     stab    *iodev        ; point to host
  2207.     jsr    init        ; initialize host
  2208.     bra    termres        ; restore terminal
  2209. hostin:    ldab    *iodev        ; save terminal
  2210.     pshb
  2211.     ldab    *hostdev
  2212.     stab    *iodev        ; point to host
  2213.     jsr    input        ; read host
  2214.     bra    termres        ; restore terminal
  2215. hostout:
  2216.     ldab    *iodev        ; save terminal
  2217.     pshb
  2218.     ldab    *hostdev
  2219.     stab    *iodev        ; point to host
  2220.     jsr    output        ; write to host
  2221. termres:
  2222.     pulb            ; restore terminal device
  2223.     stab    *iodev
  2224.     rts
  2225.  
  2226.  
  2227. ;**********
  2228. ;*    load(ptrbuff[]) - load s1/s9 records from
  2229. ;*host to memory.  ptrbuff[] points to string in
  2230. ;*input buffer which is a command to output s1/s9
  2231. ;*records from the host ("cat filename" for unix).
  2232. ;*    returns error and address if it can't write
  2233. ;*to a particular location.
  2234. ;**********
  2235. ;*    verify(ptrbuff[]) - verify memory from load
  2236. ;*command.  ptrbuff[] is same as for load.
  2237. ;**********
  2238. verify:    clr    *tmp2
  2239.     inc    *tmp2        ; flagt1 = 1 = verify
  2240.     bra    load1
  2241. load:    clr    *tmp2        ; flagt1 = 0 = load
  2242.  
  2243.  
  2244. ;*a=wskip();
  2245. ;*if(a = cr) goto transparent mode;
  2246. ;*if(t option) hostdev = iodev;
  2247.  
  2248. load1:    jsr    wskip
  2249.     cmpa    #0x0d
  2250.     bne    load1a
  2251.     jmp    host        ; go to host if no args
  2252. load1a:    jsr    upcase
  2253.     cmpa    #'T        ; look for t option
  2254.     bne    load1b        ; jump not t option
  2255.     jsr    incbuff
  2256.     jsr    readbuff    ; get next character
  2257.     jsr    decbuff
  2258.     cmpa    #0x0d
  2259.     bne    load1b        ; jump if not t option
  2260.     clr    *autolf
  2261.     ldaa    *iodev
  2262.     staa    *hostdev        ; set host port = terminal
  2263.     bra    load6        ; go wait for s1 records
  2264.  
  2265. ;*else while(not cr)
  2266. ;*    read character from input buffer;
  2267. ;*    send character to host;
  2268.  
  2269. load1b:    clr    *autolf
  2270.     jsr    hostco        ; connect sci (evb board)
  2271.     jsr    hostinit    ; initialize host port
  2272. load2:    jsr    readbuff    ; get next char
  2273.     jsr    incbuff
  2274.     psha            ; save char
  2275.     jsr    hostout        ; output to host
  2276.     jsr    output        ; echo to terminal
  2277.     pula
  2278.     cmpa    #0x0d
  2279.     bne    load2        ; jump if not cr
  2280.  
  2281. ;*repeat:
  2282. ;*    if(hostdev != iodev) check abort;
  2283. ;*    a = hostin();
  2284. ;*    if(a = 's')
  2285. ;*        a = hostin;
  2286. ;*        if(a = '9')
  2287. ;*        read rest of record;
  2288. ;*        return(done);
  2289. ;*        if(a = '1')
  2290. ;*        checksum = 0;
  2291. ;*        byte(); b = shftreg+1;    /* byte count */
  2292. ;*        byte(); byte(); x = shftreg; /* base addr*/
  2293. ;*        do
  2294. ;*            byte();
  2295. ;*            if(flagt1 = 0)
  2296. ;*            x[0] = shftreg+1
  2297. ;*            if(x[0] != shftreg+1)
  2298. ;*                return("rom-(x)");
  2299. ;*            x++; b--;
  2300. ;*        until(b = 0)
  2301.  
  2302. load6    = .
  2303.     ldaa    *hostdev
  2304.     cmpa    *iodev
  2305.     beq    load65        ; jump if hostdev=iodev
  2306.     jsr    chkabrt        ; check for abort
  2307. load65:    jsr    hostin        ; read host
  2308.     tsta
  2309.     beq    load6        ; jump if no input
  2310.     cmpa    #'S
  2311.     bne    load6        ; jump if not s
  2312. load7:    jsr    hostin        ; read host
  2313.     tsta
  2314.     beq    load7        ; jump if no input
  2315.     cmpa    #'9
  2316.     bne    load8        ; jump if not s9
  2317.     jsr    byte
  2318.     ldab    *shftreg+1    ; b = byte count
  2319. load75:    jsr    byte
  2320.     decb
  2321.     bne    load75        ; loop until end of record
  2322.     inc    *autolf        ; turn on autolf
  2323.     jsr    targco        ; disconnect sci (evb)
  2324.     ldx    #msg11        ; "done"
  2325.     jsr    outstrg
  2326.     rts
  2327. load8:    cmpa    #'1
  2328.     bne    load6        ; jump if not s1
  2329.     clr    *tmp4        ; clear checksum
  2330.     jsr    byte
  2331.     ldab    *shftreg+1
  2332.     subb    #0x2        ; b = byte count
  2333.     jsr    byte
  2334.     jsr    byte
  2335.     ldx    *shftreg    ; x = base address
  2336.     dex
  2337. load10:    jsr    byte        ; get next byte
  2338.     inx
  2339.     decb            ; check byte count
  2340.     beq    load12        ; if 0, go do checksum
  2341.     ldaa    *shftreg+1
  2342.     tst    *tmp2
  2343.     bne    load11        ; jump if verify
  2344.     staa    0,x        ; load only
  2345. load11:    cmpa    0,x        ; verify ram location
  2346.     beq    load10        ; jump if ram ok
  2347.     stx    *ptr3        ; save error address
  2348.     inc    *autolf        ; turn on autolf
  2349.     jsr    targco        ; disconnect sci(evb)
  2350.     jsr    outcrlf
  2351.     ldx    #msg13        ; "error addr"
  2352.     jsr    outstrg
  2353.     ldx    #ptr3
  2354.     jsr    out2bsp        ; address
  2355.     rts
  2356. load12:    ldaa    *tmp4
  2357.     inca            ; do checksum
  2358.     bne    load13        ; jump if s1 record okay
  2359.     jmp    load6
  2360. load13:    inc    *autolf
  2361.     jsr    targco        ; disconnect sci(evb)
  2362.     jsr    outcrlf
  2363.     ldx    #msg12        ; "checksum error"
  2364.     jsr    outstrg
  2365.     rts
  2366.  
  2367. ;**********
  2368. ;*    byte() -  read 2 ascii bytes from host and
  2369. ;*convert to one hex byte.  returns byte
  2370. ;*shifted into shftreg and added to tmp4.
  2371. ;**********
  2372. byte:    pshb
  2373.     pshx
  2374. byte0:    jsr    hostin        ; read host (1st byte)
  2375.     tsta
  2376.     beq    byte0        ; loop until input
  2377.     jsr    hexbin
  2378. byte1:    jsr    hostin        ; read host (2nd byte)
  2379.     tsta
  2380.     beq    byte1        ; loop until input
  2381.     jsr    hexbin
  2382.     ldaa    *shftreg+1
  2383.     adda    *tmp4
  2384.     staa    *tmp4        ; add to checksum
  2385.     pulx
  2386.     pulb
  2387.     rts
  2388.  
  2389.  
  2390. ;*******************************************
  2391. ;*    memory [<addr>]
  2392. ;*    [<addr>]/
  2393. ;* opens memory and allows user to modify the
  2394. ;*contents at <addr> or the last opened location.
  2395. ;*    subcommands:
  2396. ;* [<data>]<cr> - close current location and exit.
  2397. ;* [<data>]<lf> - close current and open next.
  2398. ;* [<data>]<^> - close current and open previous.
  2399. ;* [<data>]<sp> - close current and open next.
  2400. ;* [<data>]/ - reopen current location.
  2401. ;*    the contents of the current location is only
  2402. ;*    changed if valid data is entered before each
  2403. ;*  subcommand.
  2404. ;* [<addr>]o - compute relative offset from current
  2405. ;*    location to <addr>.  the current location must
  2406. ;*    be the address of the offset byte.
  2407. ;**********
  2408. ;*a = wskip();
  2409. ;*if(a != cr)
  2410. ;*    a = buffarg();
  2411. ;*    if(a != cr) return(bad argument);
  2412. ;*    if(countu1 != 0) ptrmem[] = shftreg;
  2413.  
  2414. memory:    jsr    wskip
  2415.     cmpa    #0xd
  2416.     beq    mem1        ; jump if cr
  2417.     jsr    buffarg
  2418.     jsr    wskip
  2419.     cmpa    #0xd
  2420.     beq    mslash        ; jump if cr
  2421.     ldx    #msg9        ; "bad argument"
  2422.     jsr    outstrg
  2423.     rts
  2424. mslash:    tst    *count
  2425.     beq    mem1        ; jump if no argument
  2426.     ldx    *shftreg
  2427.     stx    *ptrmem        ; update "current location"
  2428.  
  2429. ;**********
  2430. ;* subcommands
  2431. ;**********
  2432. ;*outcrlf();
  2433. ;*out2bsp(ptrmem[]);
  2434. ;*out1bsp(ptrmem[0]);
  2435.  
  2436. mem1:    jsr    outcrlf
  2437. mem2:    ldx    #ptrmem
  2438.     jsr    out2bsp        ; output address
  2439. mem3:    ldx    *ptrmem
  2440.     jsr    out1bsp        ; output contents
  2441.     clr    *shftreg
  2442.     clr    *shftreg+1
  2443. ;*while 1
  2444. ;*a = termarg();
  2445. ;*    switch(a)
  2446. ;*        case(space):
  2447. ;*        chgbyt();
  2448. ;*        ptrmem[]++;
  2449. ;*        case(linefeed):
  2450. ;*        chgbyt();
  2451. ;*        ptrmem[]++;
  2452. ;*        case(up arrow):
  2453. ;*        case(backspace):
  2454. ;*        chgbyt();
  2455. ;*        ptrmem[]--;
  2456. ;*        case("/"):
  2457. ;*        chgbyt();
  2458. ;*        outcrlf();
  2459. ;*        case(o):
  2460. ;*        d = ptrmem[0] - (shftreg);
  2461. ;*        if(0x80 < d < 0xff81)
  2462. ;*            print(out of range);
  2463. ;*        countt1 = d-1;
  2464. ;*        out1bsp(countt1);
  2465. ;*        case(carriage return):
  2466. ;*        chgbyt();
  2467. ;*        return;
  2468. ;*        default: return(command?)
  2469.  
  2470. mem4:    jsr    termarg
  2471.     jsr    upcase
  2472.     ldx    *ptrmem
  2473.     cmpa    #0x20
  2474.     beq    memsp        ; jump if space
  2475.     cmpa    #0x0a
  2476.     beq    memlf        ; jump if linefeed
  2477.     cmpa    #0x5e
  2478.     beq    memua        ; jump if up arrow
  2479.     cmpa    #0x08
  2480.     beq    membs        ; jump if backspace
  2481.     cmpa    #'/
  2482.     beq    memsl        ; jump if /
  2483.     cmpa    #'O
  2484.     beq    memoff        ; jump if o
  2485.     cmpa    #0x0d
  2486.     beq    memcr        ; jump if carriage ret
  2487.     ldx    #msg8        ; "command?"
  2488.     jsr    outstrg
  2489.     jmp    mem1
  2490. memsp:    jsr    chgbyt
  2491.     inx
  2492.     stx    *ptrmem
  2493.     jmp    mem3        ; output contents
  2494. memlf:    jsr    chgbyt
  2495.     inx
  2496.     stx    *ptrmem
  2497.     jmp    mem2        ; output addr, contents
  2498. memua    = .
  2499. membs:    jsr    chgbyt
  2500.     dex
  2501.     stx    *ptrmem
  2502.     jmp    mem1        ; output cr, addr, contents
  2503. memsl:    jsr    chgbyt
  2504.     jmp    mem1        ; output cr, addr, contents
  2505. memoff:    ldd    *shftreg    ; destination addr
  2506.     subd    *ptrmem
  2507.     cmpa    #0x0
  2508.     bne    memoff1        ; jump if not 0
  2509.     cmpb    #0x80
  2510.     bls    memoff3        ; jump if in range
  2511.     bra    memoff2        ; out of range
  2512. memoff1:
  2513.     cmpa    #0xff
  2514.     bne    memoff2        ; out of range
  2515.     cmpb    #0x81
  2516.     bhs    memoff3        ; in range
  2517. memoff2:
  2518.     ldx    #msg3        ; "too long"
  2519.     jsr    outstrg
  2520.     jmp    mem1        ; output cr, addr, contents
  2521. memoff3:
  2522.     subd    #0x1        ; b now has offset
  2523.     stab    *tmp4
  2524.     jsr    outspac
  2525.     ldx    #tmp4
  2526.     jsr    out1bsp        ; output offset
  2527.     jmp    mem1        ; output cr, addr, contents
  2528. memcr:    jsr    chgbyt
  2529.     rts            ; exit task
  2530.  
  2531.  
  2532. ;**********
  2533. ;*    move <src1> <src2> [<dest>]    - move
  2534. ;*block at <src1> to <src2> to <dest>.
  2535. ;*    moves block 1 byte up if no <dest>.
  2536. ;**********
  2537. ;*a = buffarg();
  2538. ;*if(countu1 = 0) return(bad argument);
  2539. ;*if( !wchek(a) ) return(bad argument);
  2540. ;*ptr1 = shftreg;    /* src1 */
  2541.  
  2542. move    = .
  2543.     jsr    buffarg
  2544.     tst    *count
  2545.     beq    moverr        ; jump if no arg
  2546.     jsr    wchek
  2547.     bne    moverr        ; jump if no delim
  2548.     ldx    *shftreg    ; src1
  2549.     stx    *ptr1
  2550.  
  2551. ;*a = buffarg();
  2552. ;*if(countu1 = 0) return(bad argument);
  2553. ;*if( !dchek(a) ) return(bad argument);
  2554. ;*ptr2 = shftreg;    /* src2 */
  2555.  
  2556.     jsr    buffarg
  2557.     tst    *count
  2558.     beq    moverr        ; jump if no arg
  2559.     jsr    dchek
  2560.     bne    moverr        ; jump if no delim
  2561.     ldx    *shftreg    ; src2
  2562.     stx    *ptr2
  2563.  
  2564. ;*a = buffarg();
  2565. ;*a = wskip();
  2566. ;*if(a != cr) return(bad argument);
  2567. ;*if(countu1 != 0) tmp2 = shftreg;  /* dest */
  2568. ;*else tmp2 = ptr1 + 1;
  2569.  
  2570.     jsr    buffarg
  2571.     jsr    wskip
  2572.     cmpa    #0x0d
  2573.     bne    moverr        ; jump if not cr
  2574.     tst    *count
  2575.     beq    move1        ; jump if no arg
  2576.     ldx    *shftreg    ; dest
  2577.     bra    move2
  2578. moverr:    ldx    #msg9        ; "bad argument"
  2579.     jsr    outstrg
  2580.     rts
  2581. move1:    ldx    *ptr1
  2582.     inx            ; default dest
  2583. move2:    stx    *ptr3
  2584.  
  2585. ;*if(src1 < dest <= src2)
  2586. ;*    dest = dest+(src2-src1);
  2587. ;*    for(x = src2; x = src1; x--)
  2588. ;*        dest[0]-- = x[0]--;
  2589.  
  2590.     ldx    *ptr3        ; dest
  2591.     cpx    *ptr1        ; src1
  2592.     bls    move3        ; jump if dest =< src1
  2593.     cpx    *ptr2        ; src2
  2594.     bhi    move3        ; jump if dest > src2
  2595.     ldd    *ptr2
  2596.     subd    *ptr1
  2597.     addd    *ptr3
  2598.     std    *ptr3        ; dest = dest+(src2-src1)
  2599.     ldx    *ptr2
  2600. movelp1:
  2601.     jsr    chkabrt        ; check for abort
  2602.     ldaa    ,x        ; char at src2
  2603.     pshx
  2604.     ldx    *ptr3
  2605.     cpx    #0xb600        ; jump if not eeprom
  2606.     blo    movea
  2607.     cpx    #0xb7ff        ; jump if not eeprom
  2608.     bhi    movea
  2609.     jsr    movprog        ; program eeprom
  2610. movea:    staa    ,x        ; dest
  2611.     dex
  2612.     stx    *ptr3
  2613.     pulx
  2614.     cpx    *ptr1
  2615.     beq    movrts
  2616.     dex
  2617.     bra    movelp1        ; loop src2 - src1 times
  2618. ;*
  2619. ;* else
  2620. ;*    for(x=src1; x=src2; x++)
  2621. ;*        dest[0]++ = x[0]++;
  2622.  
  2623.  
  2624. move3:    ldx    *ptr1        ; srce1
  2625. movelp2:
  2626.     jsr    chkabrt        ; check for abort
  2627.     ldaa    ,x
  2628.     pshx
  2629.     ldx    *ptr3        ; dest
  2630.     cpx    #0xb600        ; jump if not eeprom
  2631.     blo    moveb
  2632.     cpx    #0xb7ff        ; jump if not eeprom
  2633.     bhi    moveb
  2634.     jsr    movprog        ; program eeprom
  2635. moveb:    staa    ,x
  2636.     inx
  2637.     stx    *ptr3
  2638.     pulx
  2639.     cpx    *ptr2
  2640.     beq    movrts
  2641.     inx
  2642.     bra    movelp2        ; loop src2-src1 times
  2643. movrts:    rts
  2644.  
  2645. ;*************
  2646. ;*    movprog - program eeprom location in x with
  2647. ;*    data in a.
  2648. ;*************
  2649. movprog:
  2650.     pshb
  2651.     pshx
  2652.     ldab    #0x02
  2653.     stab    pprog        ; set eelat
  2654.     staa    ,x
  2655.     ldab    #0x03
  2656.     bne    acl4
  2657.     clrb            ; fail safe
  2658. acl4:    stab    pprog        ; set pgm
  2659.     ldx    #0x0d06
  2660. movedly:
  2661.     dex
  2662.     bne    movedly        ; delay 10 ms at E = 2 mhz
  2663.     ldab    #0x00
  2664.     stab    pprog
  2665.     pulx
  2666.     pulb
  2667.     rts
  2668.  
  2669.  
  2670. ;**********
  2671. ;*    register [<name>]    - prints the user regs
  2672. ;*and opens them for modification.    <name> is
  2673. ;*the first register opened (default = p).
  2674. ;*    subcommands:
  2675. ;* [<nn>]<space>    opens the next register.
  2676. ;* [<nn>]<cr>    return.
  2677. ;*    the register value is only changed if
  2678. ;*    <nn> is entered before the subcommand.
  2679. ;**********
  2680. ;*x[] = reglist
  2681. ;*a = wskip(); a = upcase(a);
  2682. ;*if(a != cr)
  2683. ;*    while( a != x[0] )
  2684. ;*        if( x[0] = "s") return(bad argument);
  2685. ;*        x[]++;
  2686. ;*    incbuff(); a = wskip();
  2687. ;*    if(a != cr) return(bad argument);
  2688.  
  2689. register:
  2690.     ldx    #reglist
  2691.     jsr    wskip        ; a = first char of arg
  2692.     jsr    upcase        ; convert to upper case
  2693.     cmpa    #0xd
  2694.     beq    reg4        ; jump if no argument
  2695. reg1:    cmpa    0,x
  2696.     beq    reg3
  2697.     ldab    0,x
  2698.     inx
  2699.     cmpb    #'S
  2700.     bne    reg1        ; jump if not "s"
  2701. reg2:    ldx    #msg9        ; "bad argument"
  2702.     jsr    outstrg
  2703.     rts
  2704. reg3:    pshx
  2705.     jsr    incbuff
  2706.     jsr    wskip        ; next char after arg
  2707.     cmpa    #0xd
  2708.     pulx
  2709.     bne    reg2        ; jump if not cr
  2710.  
  2711. ;*rprint();
  2712. ;*    while(x[0] != "s")
  2713. ;*        rprnt1(x);
  2714. ;*        a = termarg();    /* read from terminal */
  2715. ;*        if( ! dchek(a) ) return(bad argument);
  2716. ;*        if(countu1 != 0)
  2717. ;*        if(x[14] = 1)
  2718. ;*            regs[x[7]++ = shftreg;
  2719. ;*        regs[x[7]] = shftreg+1;
  2720. ;*        if(a = cr) break;
  2721. ;*return;
  2722.  
  2723. reg4:    jsr    rprint        ; print all registers
  2724. reg5:    jsr    outcrlf
  2725.     jsr    rprnt1        ; print reg name
  2726.     clr    *shftreg
  2727.     clr    *shftreg+1
  2728.     jsr    termarg        ; read subcommand
  2729.     jsr    dchek
  2730.     beq    reg6        ; jump if delimeter
  2731.     ldx    #msg9        ; "bad argument"
  2732.     jsr    outstrg
  2733.     rts
  2734. reg6:    psha
  2735.     pshx
  2736.     tst    *count
  2737.     beq    reg8        ; jump if no input
  2738.     ldab    7,x        ; get reg offset
  2739.     ldaa    14,x        ; byte size
  2740.     ldx    #regs        ; user registers
  2741.     abx
  2742.     tsta
  2743.     beq    reg7        ; jump if 1 byte reg
  2744.     ldaa    *shftreg
  2745.     staa    0,x        ; put in top byte
  2746.     inx
  2747. reg7:    ldaa    *shftreg+1
  2748.     staa    0,x        ; put in bottom byte
  2749. reg8:    pulx
  2750.     pula
  2751.     ldab    0,x        ; check for register s
  2752.     cmpb    #'S
  2753.     beq    reg9        ; jump if "s"
  2754.     inx            ; point to next register
  2755.     cmpa    #0xd
  2756.     bne    reg5        ; jump if not cr
  2757. reg9:    rts
  2758.  
  2759. page1    =    0x00        ; values for page opcodes
  2760. page2    =    0x18
  2761. page3    =    0x1a
  2762. page4    =    0xcd
  2763. immed    =    0x0        ; addressing modes
  2764. indx    =    0x1
  2765. indy    =    0x2
  2766. limmed    =    0x3        ; (long immediate)
  2767. other    =    0x4
  2768.  
  2769. ;*** rename variables for assem/disassem ***
  2770. amode    =    tmp2        ; addressing mode
  2771. yflag    =    tmp3
  2772. pnorm    =    tmp4        ; page for normal opcode
  2773. oldpc    =    ptrmem
  2774. pc    =    ptr1        ; program counter
  2775. px    =    ptr2        ; page for x indexed
  2776. py    =    ptr2+1        ; page for y indexed
  2777. baseop    =    ptr3        ; base opcode
  2778. class    =    ptr3+1        ; class
  2779. dispc    =    ptr4        ; pc for disassembler
  2780. braddr    =    ptr5        ; relative branch offset
  2781. mneptr    =    ptr6        ; pointer to table for dis
  2782. asscomm    =    ptr7        ; subcommand for assembler
  2783.  
  2784. ;*** error messages for assembler ***
  2785. msgdir:    .word    #msga1        ; message table index
  2786.     .word    #msga2
  2787.     .word    #msga3
  2788.     .word    #msga4
  2789.     .word    #msga5
  2790.     .word    #msga6
  2791.     .word    #msga7
  2792.     .word    #msga8
  2793.     .word    #msga9
  2794. msga1:    .ascii    'Immediate mode illegal'
  2795.     .byte    eot
  2796. msga2:    .ascii    'Error in mnemonic table'
  2797.     .byte    eot
  2798. msga3:    .ascii    'Illegal bit op'
  2799.     .byte    eot
  2800. msga4:    .ascii    'Bad argument'
  2801.     .byte    eot
  2802. msga5:    .ascii    'Mnemonic not found'
  2803.     .byte    eot
  2804. msga6:    .ascii    'Unknown addressing mode'
  2805.     .byte    eot
  2806. msga7:    .ascii    'Indexed addressing assumed'
  2807.     .byte    eot
  2808. msga8:    .ascii    'Syntax error'
  2809.     .byte    eot
  2810. msga9:    .ascii    'Branch out of range'
  2811.     .byte    eot
  2812.  
  2813. ;****************
  2814. ;*    assem(addr) -68hc11 line assembler/disassembler.
  2815. ;*    this routine will disassemble the opcode at
  2816. ;*<addr> and then allow the user to enter a line for
  2817. ;*assembly. rules for assembly are as follows:
  2818. ;* -a '#' sign indicates immediate addressing.
  2819. ;* -a ',' (comma) indicates indexed addressing
  2820. ;*    and the next character must be x or y.
  2821. ;* -all arguments are assumed to be hex and the
  2822. ;*    '$' sign shouldn't be used.
  2823. ;* -arguments should be separated by 1 or more
  2824. ;*    spaces or tabs.
  2825. ;* -any input after the required number of
  2826. ;*    arguments is ignored.
  2827. ;* -upper or lower case makes no difference.
  2828. ;*
  2829. ;*    to signify end of input line, the following
  2830. ;*commands are available and have the indicated action:
  2831. ;*    <cr>  -carriage return finds the next opcode for
  2832. ;*        assembly.  if there was no assembly input,
  2833. ;*        the next opcode disassembled is retrieved
  2834. ;*        from the disassembler.
  2835. ;*    <lf>  -linefeed works the same as carriage return
  2836. ;*        except if there was no assembly input, the
  2837. ;*        <addr> is incremented and the next <addr> is
  2838. ;*        disassembled.
  2839. ;*    '^'  -up arrow decrements <addr> and the previous
  2840. ;*        address is then disassembled.
  2841. ;*    '/'  -slash redisassembles the current address.
  2842. ;*
  2843. ;*    to exit the assembler use control a.  of course
  2844. ;*control x and del will also allow you to abort.
  2845. ;**********
  2846. ;*oldpc = rambase;
  2847. ;*a = wskip();
  2848. ;*if (a != cr)
  2849. ;*    buffarg()
  2850. ;*    a = wskip();
  2851. ;*    if ( a != cr ) return(error);
  2852. ;*    oldpc = a;
  2853.  
  2854. assem    = .
  2855.     ldx    #rambs
  2856.     stx    *oldpc
  2857.     jsr    wskip
  2858.     cmpa    #0x0d
  2859.     beq    assloop     ; jump if no argument
  2860.     jsr    buffarg
  2861.     jsr    wskip
  2862.     cmpa    #0x0d
  2863.     beq    assem1        ; jump if argument ok
  2864.     ldx    #msga4        ; "bad argument"
  2865.     jsr    outstrg
  2866.     rts
  2867. assem1:    ldx    *shftreg
  2868.     stx    *oldpc
  2869.  
  2870. ;*repeat
  2871. ;*    pc = oldpc;
  2872. ;*    out2bsp(pc);
  2873. ;*    disassem();
  2874. ;*    a=readln();
  2875. ;*    asscomm = a;    /* save command */
  2876. ;*    if(a == ('^' or '/')) outcrlf;
  2877. ;*    if(a == 0) return(error);
  2878.  
  2879. assloop:
  2880.     ldx    *oldpc
  2881.     stx    *pc
  2882.     jsr    outcrlf
  2883.     ldx    #pc
  2884.     jsr    out2bsp        ; output the address
  2885.     jsr    disassm        ; disassemble opcode
  2886.     jsr    outcrlf
  2887.     jsr    outspac
  2888.     jsr    outspac
  2889.     jsr    outspac
  2890.     jsr    outspac
  2891.     ldaa    #prompt        ; prompt user
  2892.     jsr    outa        ; output prompt character
  2893.     jsr    readln        ; read input for assembly
  2894.     staa    *asscomm
  2895.     cmpa    #'^
  2896.     beq    asslp0        ; jump if up arrow
  2897.     cmpa    #'/
  2898.     beq    asslp0        ; jump if slash
  2899.     cmpa    #0x00
  2900.     bne    asslp1        ; jump if none of above
  2901.     rts            ; return if bad input
  2902. asslp0:    jsr    outcrlf
  2903. asslp1    = .
  2904.     jsr    outspac
  2905.     jsr    outspac
  2906.     jsr    outspac
  2907.     jsr    outspac
  2908.     jsr    outspac
  2909.  
  2910. ;*    b = parse(input); /* get mnemonic */
  2911. ;*    if(b > 5) print("not found"); asscomm='/';
  2912. ;*    elseif(b >= 1)
  2913. ;*    msrch();
  2914. ;*    if(class==0xff)
  2915. ;*    print("not found"); asscomm='/';
  2916. ;*    else
  2917. ;*    a = doop(opcode,class);
  2918. ;*    if(a == 0) dispc=0;
  2919. ;*    else process error; asscomm='/';
  2920.  
  2921.     jsr    parse
  2922.     cmpb    #0x5
  2923.     ble    asslp2        ; jump if mnemonic <= 5 chars
  2924.     ldx    #msga5        ; "mnemonic not found"
  2925.     jsr    outstrg
  2926.     bra    asslp5
  2927. asslp2    = .
  2928.     cmpb    #0x0
  2929.     beq    asslp10     ; jump if no input
  2930.     jsr    msrch
  2931.     ldaa    *class
  2932.     cmpa    #0xff
  2933.     bne    asslp3
  2934.     ldx    #msga5        ; "mnemonic not found"
  2935.     jsr    outstrg
  2936.     bra    asslp5
  2937. asslp3:    jsr    doop
  2938.     cmpa    #0x00
  2939.     bne    asslp4        ; jump if doop error
  2940.     ldx    #0x00
  2941.     stx    *dispc        ; indicate good assembly
  2942.     bra    asslp10
  2943. asslp4:    deca            ; a = error message index
  2944.     tab
  2945.     ldx    #msgdir
  2946.     abx
  2947.     abx
  2948.     ldx    0,x
  2949.     jsr    outstrg     ; output error message
  2950. asslp5:    clr    *asscomm     ; error command
  2951.  
  2952. ;*    /* compute next address - asscomm holds subcommand
  2953. ;*    and dispc indicates if valid assembly occured. */
  2954. ;*  if(asscomm=='^') oldpc -= 1;
  2955. ;*  if(asscomm==(lf or cr)
  2956. ;*    if(dispc==0) oldpc=pc;
  2957. ;*    else
  2958. ;*    if(asscomm==lf) dispc=oldpc+1;
  2959. ;*    oldpc=dispc;
  2960. ;*until(eot)
  2961.  
  2962.  
  2963. asslp10    = .
  2964.     ldaa    *asscomm
  2965.     cmpa    #'^
  2966.     bne    asslp11        ; jump if not up arrow
  2967.     ldx    *oldpc
  2968.     dex
  2969.     stx    *oldpc        ; back up
  2970.     bra    asslp15
  2971. asslp11:
  2972.     cmpa    #0x0a
  2973.     beq    asslp12        ; jump if linefeed
  2974.     cmpa    #0x0d
  2975.     bne    asslp15        ; jump if not cr
  2976. asslp12:
  2977.     ldx    *dispc
  2978.     bne    asslp13        ; jump if dispc != 0
  2979.     ldx    *pc
  2980.     stx    *oldpc
  2981.     bra    asslp15
  2982. asslp13:
  2983.     cmpa    #0x0a
  2984.     bne    asslp14        ; jump if not linefeed
  2985.     ldx    *oldpc
  2986.     inx
  2987.     stx    *dispc
  2988. asslp14:
  2989.     ldx    *dispc
  2990.     stx    *oldpc
  2991. asslp15:
  2992.     jmp    assloop
  2993.  
  2994. ;****************
  2995. ;*    readln() --- read input from terminal into buffer
  2996. ;* until a command character is read (cr,lf,/,^).
  2997. ;* if more chars are typed than the buffer will hold,
  2998. ;* the extra characters are overwritten on the end.
  2999. ;*  on exit: b=number of chars read, a=0 if quit,
  3000. ;* else a=next command.
  3001. ;****************
  3002. ;*for(b==0;b<=bufflng;b++) inbuff[b] = cr;
  3003.  
  3004. readln:    clrb
  3005.     ldaa    #0x0d        ; carriage ret
  3006. rln0:    ldx    #inbuff
  3007.     abx
  3008.     staa    0,x        ; initialize input buffer
  3009.     incb
  3010.     cmpb    #bufflng
  3011.     blt    rln0
  3012. ;*b=0;
  3013. ;*repeat
  3014. ;*    if(a == (ctla, cntlc, cntld, cntlx, del))
  3015. ;*    return(a=0);
  3016. ;*  if(a == backspace)
  3017. ;*    if(b > 0) b--;
  3018. ;*    else b=0;
  3019. ;*  else  inbuff[b] = upcase(a);
  3020. ;*  if(b < bufflng) b++;
  3021. ;*until (a == (cr,lf,^,/))
  3022. ;*return(a);
  3023.  
  3024.     clrb
  3025. rln1:    jsr    inchar
  3026.     cmpa    #del        ; delete
  3027.     beq    rlnquit
  3028.     cmpa    #ctlx        ; control x
  3029.     beq    rlnquit
  3030.     cmpa    #ctla        ; control a
  3031.     beq    rlnquit
  3032.     cmpa    #0x03        ; control c
  3033.     beq    rlnquit
  3034.     cmpa    #0x04        ; control d
  3035.     beq    rlnquit
  3036.     cmpa    #0x08        ; backspace
  3037.     bne    rln2
  3038.     decb
  3039.     bgt    rln1
  3040.     bra    readln        ; start over
  3041. rln2:    ldx    #inbuff
  3042.     abx
  3043.     jsr    upcase
  3044.     staa    0,x        ; put char in buffer
  3045.     cmpb    #bufflng    ; max buffer length
  3046.     bge    rln3        ; jump if buffer full
  3047.     incb            ; move buffer pointer
  3048. rln3:    jsr    asschek     ; check for subcommand
  3049.     bne    rln1
  3050.     rts
  3051. rlnquit:
  3052.     clra            ; quit
  3053.     rts            ; return
  3054.  
  3055.  
  3056. ;**********
  3057. ;*    parse() -parse out the mnemonic from inbuff
  3058. ;* to combuff. on exit: b=number of chars parsed.
  3059. ;**********
  3060. ;*combuff[3] = <space>;    initialize 4th character to space.
  3061. ;*ptrbuff[] = inbuff[];
  3062. ;*a=wskip();
  3063. ;*for (b = 0; b = 5; b++)
  3064. ;*    a=readbuff(); incbuff();
  3065. ;*    if (a = (cr,lf,^,/,wspace)) return(b);
  3066. ;*    combuff[b] = upcase(a);
  3067. ;*return(b);
  3068.  
  3069. parse:    ldaa    #0x20
  3070.     staa    *combuff+3
  3071.     ldx    #inbuff        ; initialize buffer ptr
  3072.     stx    *ptr0
  3073.     jsr    wskip        ; find first character
  3074.     clrb
  3075. parslp:    jsr    readbuff    ; read character
  3076.     jsr    incbuff
  3077.     jsr    wchek
  3078.     beq    parsrt        ; jump if whitespace
  3079.     jsr    asschek
  3080.     beq    parsrt        ; jump if end of line
  3081.     jsr    upcase        ; convert to upper case
  3082.     ldx    #combuff
  3083.     abx
  3084.     staa    0,x        ; store in combuff
  3085.     incb
  3086.     cmpb    #0x5
  3087.     ble    parslp        ; loop 6 times
  3088. parsrt:    rts
  3089.  
  3090.  
  3091. ;****************
  3092. ;*    asschek() -perform compares for
  3093. ;* cr, lf, ^, /
  3094. ;****************
  3095. asschek:
  3096.     cmpa    #0x0a        ; linefeed
  3097.     beq    asschk1
  3098.     cmpa    #0x0d        ; carriage ret
  3099.     beq    asschk1
  3100.     cmpa    #'^        ; up arrow
  3101.     beq    asschk1
  3102.     cmpa    #'/        ; slash
  3103. asschk1:
  3104.     rts
  3105.  
  3106.  
  3107. ;*********
  3108. ;*    msrch() --- search mnetabl for mnemonic in combuff.
  3109. ;*stores base opcode at baseop and class at class.
  3110. ;*  class = ff if not found.
  3111. ;**********
  3112. ;*while ( != eof )
  3113. ;*    if (combuff[0-3] = mnetabl[0-3])
  3114. ;*    return(mnetabl[4],mnetabl[5]);
  3115. ;*    else *mnetabl =+ 6
  3116.  
  3117. msrch:    ldx    #mnetabl    ; pointer to mnemonic table
  3118.     ldy    #combuff    ; pointer to string
  3119.     bra    msrch1
  3120. msnext    = .
  3121.     ldab    #6
  3122.     abx            ; point to next table entry
  3123. msrch1:    ldaa    0,x        ; read table
  3124.     cmpa    #eot
  3125.     bne    msrch2        ; jump if not end of table
  3126.     ldaa    #0xff
  3127.     staa    *class        ; ff = not in table
  3128.     rts
  3129. msrch2:    cmpa    0,y        ; op[0] = tabl[0] ?
  3130.     bne    msnext
  3131.     ldaa    1,x
  3132.     cmpa    1,y        ; op[1] = tabl[1] ?
  3133.     bne    msnext
  3134.     ldaa    2,x
  3135.     cmpa    2,y        ; op[2] = tabl[2] ?
  3136.     bne    msnext
  3137.     ldaa    3,x
  3138.     cmpa    3,y        ; op[2] = tabl[2] ?
  3139.     bne    msnext
  3140.     ldd    4,x        ; opcode, class
  3141.     staa    *baseop
  3142.     stab    *class
  3143.     rts
  3144.  
  3145. ;**********
  3146. ;**    doop(baseop,class) --- process mnemonic.
  3147. ;**    on exit: a=error code corresponding to error
  3148. ;**                    messages.
  3149. ;**********
  3150. ;*amode = other; /* addressing mode */
  3151. ;*yflag = 0;    /* ynoimm, nlimm, and cpd flag */
  3152. ;*x[] = ptrbuff[]
  3153.  
  3154. doop    = .
  3155.     ldaa    #other
  3156.     staa    *amode        ; mode
  3157.     clr    *yflag
  3158.     ldx    *ptr0
  3159.  
  3160. ;*while (*x != end of buffer)
  3161. ;*    if (x[0]++ == ',')
  3162. ;*    if (x[0] == 'y') amode = indy;
  3163. ;*    else amod = indx;
  3164. ;*    break;
  3165. ;*a = wskip()
  3166. ;*if( a == '#' ) amode = immed;
  3167.  
  3168. doplp1:    cpx    #endbuff    ; (end of buffer)
  3169.     beq    doop1        ; jump if end of buffer
  3170.     ldd    0,x        ; read 2 chars from buffer
  3171.     inx            ; move pointer
  3172.     cmpa    #',
  3173.     bne    doplp1
  3174.     cmpb    #'Y        ; look for ",y"
  3175.     bne    doplp2
  3176.     ldaa    #indy
  3177.     staa    *amode
  3178.     bra    doop1
  3179. doplp2:    cmpb    #'X        ; look for ",x"
  3180.     bne    doop1        ; jump if not x
  3181.     ldaa    #indx
  3182.     staa    *amode
  3183.     bra    doop1
  3184. doop1:    jsr    wskip
  3185.     cmpa    #'#        ; look for immediate mode
  3186.     bne    doop2
  3187.     jsr    incbuff     ; point at argument
  3188.     ldaa    #immed
  3189.     staa    *amode
  3190. doop2    = .
  3191.  
  3192. ;*switch(class)
  3193.     ldab    *class
  3194.     cmpb    #p2inh
  3195.     bne    dosw1
  3196.     jmp    dop2i
  3197. dosw1:    cmpb    #inh
  3198.     bne    dosw2
  3199.     jmp    doinh
  3200. dosw2:    cmpb    #rel
  3201.     bne    dosw3
  3202.     jmp    dorel
  3203. dosw3:    cmpb    #limm
  3204.     bne    dosw4
  3205.     jmp    dolim
  3206. dosw4:    cmpb    #nimm
  3207.     bne    dosw5
  3208.     jmp    donoi
  3209. dosw5:    cmpb    #gen
  3210.     bne    dosw6
  3211.     jmp    dogene
  3212. dosw6:    cmpb    #grp2
  3213.     bne    dosw7
  3214.     jmp    dogrp
  3215. dosw7:    cmpb    #cpd
  3216.     bne    dosw8
  3217.     jmp    docpd
  3218. dosw8:    cmpb    #xnimm
  3219.     bne    dosw9
  3220.     jmp    doxnoi
  3221. dosw9:    cmpb    #xlimm
  3222.     bne    dosw10
  3223.     jmp    doxli
  3224. dosw10:    cmpb    #ynimm
  3225.     bne    dosw11
  3226.     jmp    doynoi
  3227. dosw11:    cmpb    #ylimm
  3228.     bne    dosw12
  3229.     jmp    doyli
  3230. dosw12:    cmpb    #btb
  3231.     bne    dosw13
  3232.     jmp    dobtb
  3233. dosw13:    cmpb    #setclr
  3234.     bne    dodef
  3235.     jmp    doset
  3236.  
  3237. ;*    default: return("error in mnemonic table");
  3238.  
  3239. dodef:    ldaa    #0x2
  3240.     rts
  3241.  
  3242. ;*  case p2inh: emit(page2)
  3243.  
  3244. dop2i:    ldaa    #page2
  3245.     jsr    emit
  3246.  
  3247. ;*  case inh: emit(baseop);
  3248. ;*    return(0);
  3249.  
  3250. doinh:    ldaa    *baseop
  3251.     jsr    emit
  3252.     clra
  3253.     rts
  3254.  
  3255. ;*  case rel: a = assarg();
  3256. ;*        if(a=4) return(a);
  3257. ;*        d = address - pc + 2;
  3258. ;*        if (0x7f >= d >= 0xff82)
  3259. ;*        return (out of range);
  3260. ;*        emit(opcode);
  3261. ;*        emit(offset);
  3262. ;*        return(0);
  3263.  
  3264. dorel:    jsr    assarg
  3265.     cmpa    #0x04
  3266.     bne    dorel1        ; jump if arg ok
  3267.     rts
  3268. dorel1:    ldd    *shftreg     ; get branch address
  3269.     ldx    *pc        ; get program counter
  3270.     inx
  3271.     inx            ; point to end of opcode
  3272.     stx    *braddr
  3273.     subd    *braddr        ; calculate offset
  3274.     std    *braddr        ; save result
  3275.     cmpd    #0x7f        ; in range ?
  3276.     bls    dorel2        ; jump if in range
  3277.     cmpd    #0xff80
  3278.     bhs    dorel2        ; jump if in range
  3279.     ldaa    #0x09        ; 'out of range'
  3280.     rts
  3281. dorel2:    ldaa    *baseop
  3282.     jsr    emit        ; emit opcode
  3283.     ldaa    *braddr+1
  3284.     jsr    emit        ; emit offset
  3285.     clra            ; normal return
  3286.     rts
  3287.  
  3288. ;*    case limm: if (amode == immed) amode = limmed;
  3289.  
  3290. dolim:    ldaa    *amode
  3291.     cmpa    #immed
  3292.     bne    donoi
  3293.     ldaa    #limmed
  3294.     staa    *amode
  3295.  
  3296. ;*    case nimm: if (amode == immed)
  3297. ;*        return("immediate mode illegal");
  3298.  
  3299. donoi:    ldaa    *amode
  3300.     cmpa    #immed
  3301.     bne    dogene        ; jump if not immediate
  3302.     ldaa    #0x1        ; "immediate mode illegal"
  3303.     rts
  3304.  
  3305. ;*  case gen: dogen(baseop,amode,page1,page1,page2);
  3306. ;*        return;
  3307.  
  3308. dogene:    ldaa    #page1
  3309.     staa    *pnorm
  3310.     staa    *px
  3311.     ldaa    #page2
  3312.     staa    *py
  3313.     jsr    dogen
  3314.     rts
  3315.  
  3316. ;*  case grp2: if (amode == indy)
  3317. ;*        emit(page2);
  3318. ;*        amode = indx;
  3319. ;*        if( amode == indx )
  3320. ;*        doindx(baseop);
  3321. ;*        else a = assarg();
  3322. ;*        if(a=4) return(a);
  3323. ;*        emit(opcode+0x10);
  3324. ;*        emit(extended address);
  3325. ;*        return;
  3326.  
  3327. dogrp:    ldaa    *amode
  3328.     cmpa    #indy
  3329.     bne    dogrp1
  3330.     ldaa    #page2
  3331.     jsr    emit
  3332.     ldaa    #indx
  3333.     staa    *amode
  3334. dogrp1    = .
  3335.     ldaa    *amode
  3336.     cmpa    #indx
  3337.     bne    dogrp2
  3338.     jsr    doindex
  3339.     rts
  3340. dogrp2    = .
  3341.     ldaa    *baseop
  3342.     adda    #0x10
  3343.     jsr    emit
  3344.     jsr    assarg
  3345.     cmpa    #0x04
  3346.     beq    dogrprt     ; jump if bad arg
  3347.     ldd    *shftreg     ; extended address
  3348.     jsr    emit
  3349.     tba
  3350.     jsr    emit
  3351.     clra
  3352. dogrprt:
  3353.     rts
  3354.  
  3355. ;*  case cpd: if (amode == immed)
  3356. ;*        amode = limmed; /* cpd */
  3357. ;*        if( amode == indy ) yflag = 1;
  3358. ;*        dogen(baseop,amode,page3,page3,page4);
  3359. ;*        return;
  3360.  
  3361. docpd:    ldaa    *amode
  3362.     cmpa    #immed
  3363.     bne    docpd1
  3364.     ldaa    #limmed
  3365.     staa    *amode
  3366. docpd1:    ldaa    *amode
  3367.     cmpa    #indy
  3368.     bne    docpd2
  3369.     inc    *yflag
  3370. docpd2:    ldaa    #page3
  3371.     staa    *pnorm
  3372.     staa    *px
  3373.     ldaa    #page4
  3374.     staa    *py
  3375.     jsr    dogen
  3376.     rts
  3377.  
  3378. ;*    case xnimm: if (amode == immed)    /* stx */
  3379. ;*            return("immediate mode illegal");
  3380.  
  3381. doxnoi:    ldaa    *amode
  3382.     cmpa    #immed
  3383.     bne    doxli
  3384.     ldaa    #0x1        ; "immediate mode illegal"
  3385.     rts
  3386.  
  3387. ;*    case xlimm: if (amode == immed)    /* cpx, ldx */
  3388. ;*            amode = limmed;
  3389. ;*        dogen(baseop,amode,page1,page1,page4);
  3390. ;*        return;
  3391.  
  3392. doxli:    ldaa    *amode
  3393.     cmpa    #immed
  3394.     bne    doxli1
  3395.     ldaa    #limmed
  3396.     staa    *amode
  3397. doxli1:    ldaa    #page1
  3398.     staa    *pnorm
  3399.     staa    *px
  3400.     ldaa    #page4
  3401.     staa    *py
  3402.     jsr    dogen
  3403.     rts
  3404.  
  3405. ;*    case ynimm: if (amode == immed)    /* sty */
  3406. ;*            return("immediate mode illegal");
  3407.  
  3408. doynoi:    ldaa    *amode
  3409.     cmpa    #immed
  3410.     bne    doyli
  3411.     ldaa    #0x1        ; "immediate mode illegal"
  3412.     rts
  3413.  
  3414. ;*    case ylimm: if (amode == indy) yflag = 1;/* cpy, ldy */
  3415. ;*        if(amode == immed) amode = limmed;
  3416. ;*        dogen(opcode,amode,page2,page3,page2);
  3417. ;*        return;
  3418.  
  3419. doyli:    ldaa    *amode
  3420.     cmpa    #indy
  3421.     bne    doyli1
  3422.     inc    *yflag
  3423. doyli1:    cmpa    #immed
  3424.     bne    doyli2
  3425.     ldaa    #limmed
  3426.     staa    *amode
  3427. doyli2:    ldaa    #page2
  3428.     staa    *pnorm
  3429.     staa    *py
  3430.     ldaa    #page3
  3431.     staa    *px
  3432.     jsr    dogen
  3433.     rts
  3434.  
  3435. ;*    case btb:        /* bset, bclr */
  3436. ;*    case setclr: a = bitop(baseop,amode,class);
  3437. ;*        if(a=0) return(a = 3);
  3438. ;*        if( amode == indy )
  3439. ;*            emit(page2);
  3440. ;*            amode = indx;
  3441.  
  3442. dobtb    = .
  3443. doset:    jsr    bitop
  3444.     cmpa    #0x00
  3445.     bne    doset1
  3446.     ldaa    #0x3        ; "illegal bit op"
  3447.     rts
  3448. doset1:    ldaa    *amode
  3449.     cmpa    #indy
  3450.     bne    doset2
  3451.     ldaa    #page2
  3452.     jsr    emit
  3453.     ldaa    #indx
  3454.     staa    *amode
  3455. doset2    = .
  3456.  
  3457. ;*        emit(baseop);
  3458. ;*        a = assarg();
  3459. ;*        if(a = 4) return(a);
  3460. ;*        emit(index offset);
  3461. ;*        if( amode == indx )
  3462. ;*            buffptr += 2;    /* skip ,x or ,y */
  3463.  
  3464.     ldaa    *baseop
  3465.     jsr    emit
  3466.     jsr    assarg
  3467.     cmpa    #0x04
  3468.     bne    doset22        ; jump if arg ok
  3469.     rts
  3470. doset22:
  3471.     ldaa    *shftreg+1    ; index offset
  3472.     jsr    emit
  3473.     ldaa    *amode
  3474.     cmpa    #indx
  3475.     bne    doset3
  3476.     jsr    incbuff
  3477.     jsr    incbuff
  3478. doset3    = .
  3479.  
  3480. ;*        a = assarg();
  3481. ;*        if(a = 4) return(a);
  3482. ;*        emit(mask);    /* mask */
  3483. ;*        if( class == setclr )
  3484. ;*            return;
  3485.  
  3486.     jsr    assarg
  3487.     cmpa    #0x04
  3488.     bne    doset33        ; jump if arg ok
  3489.     rts
  3490. doset33:
  3491.     ldaa    *shftreg+1    ; mask
  3492.     jsr    emit
  3493.     ldaa    *class
  3494.     cmpa    #setclr
  3495.     bne    doset4
  3496.     clra
  3497.     rts
  3498. doset4    = .
  3499.  
  3500. ;*        a = assarg();
  3501. ;*        if(a = 4) return(a);
  3502. ;*        d = (pc+1) - shftreg;
  3503. ;*        if (0x7f >= d >= 0xff82)
  3504. ;*            return (out of range);
  3505. ;*        emit(branch offset);
  3506. ;*        return(0);
  3507.  
  3508.     jsr    assarg
  3509.     cmpa    #0x04
  3510.     bne    doset5        ; jump if arg ok
  3511.     rts
  3512. doset5:    ldx    *pc         ; program counter
  3513.     inx            ; point to next inst
  3514.     stx    *braddr        ; save pc value
  3515.     ldd    *shftreg        ; get branch address
  3516.     subd    *braddr        ; calculate offset
  3517.     cmpd    #0x7f
  3518.     bls    doset6        ; jump if in range
  3519.     cmpd    #0xff80
  3520.     bhs    doset6        ; jump if in range
  3521.     clra
  3522.     jsr    emit
  3523.     ldaa    #0x09        ; 'out of range'
  3524.     rts
  3525. doset6:    tba            ; offset
  3526.     jsr    emit
  3527.     clra
  3528.     rts
  3529.  
  3530.  
  3531. ;**********
  3532. ;**    bitop(baseop,amode,class) --- adjust opcode on bit
  3533. ;**    manipulation instructions.  returns opcode in a
  3534. ;**    or a = 0 if error
  3535. ;**********
  3536. ;*if( amode == indx || amode == indy ) return(op);
  3537. ;*if( class == setclr ) return(op-8);
  3538. ;*else if(class==btb) return(op-12);
  3539. ;*else fatal("bitop");
  3540.  
  3541. bitop    = .
  3542.     ldaa    *amode
  3543.     ldab    *class
  3544.     cmpa    #indx
  3545.     bne    bitop1
  3546.     rts
  3547. bitop1:    cmpa    #indy
  3548.     bne    bitop2        ; jump not indexed
  3549.     rts
  3550. bitop2:    cmpb    #setclr
  3551.     bne    bitop3        ; jump not bset,bclr
  3552.     ldaa    *baseop        ; get opcode
  3553.     suba    #8
  3554.     staa    *baseop
  3555.     rts
  3556. bitop3:    cmpb    #btb
  3557.     bne    bitop4        ; jump not bit branch
  3558.     ldaa    *baseop        ; get opcode
  3559.     suba    #12
  3560.     staa    *baseop
  3561.     rts
  3562. bitop4:    clra            ; 0 = fatal bitop
  3563.     rts
  3564.  
  3565. ;**********
  3566. ;**    dogen(baseop,mode,pnorm,px,py) - process
  3567. ;** general addressing modes. returns a = error    #.
  3568. ;**********
  3569. ;*pnorm = page for normal addressing modes: imm,dir,ext
  3570. ;*px = page for indx addressing
  3571. ;*py = page for indy addressing
  3572. ;*switch(amode)
  3573. dogen:    ldaa    *amode
  3574.     cmpa    #limmed
  3575.     beq    doglim
  3576.     cmpa    #immed
  3577.     beq    dogimm
  3578.     cmpa    #indy
  3579.     beq    dogindy
  3580.     cmpa    #indx
  3581.     beq    dogindx
  3582.     cmpa    #other
  3583.     beq    dogoth
  3584.  
  3585. ;*default: error("unknown addressing mode");
  3586.  
  3587. dogdef:    ldaa    #0x06        ; unknown addre...
  3588.     rts
  3589.  
  3590. ;*case limmed: epage(pnorm);
  3591. ;*        emit(baseop);
  3592. ;*        a = assarg();
  3593. ;*        if(a = 4) return(a);
  3594. ;*        emit(2 bytes);
  3595. ;*        return(0);
  3596.  
  3597. doglim:    ldaa    *pnorm
  3598.     jsr    epage
  3599. doglim1:
  3600.     ldaa    *baseop
  3601.     jsr    emit
  3602.     jsr    assarg        ; get next argument
  3603.     cmpa    #0x04
  3604.     bne    doglim2        ; jump if arg ok
  3605.     rts
  3606. doglim2:
  3607.     ldd    *shftreg
  3608.     jsr    emit
  3609.     tba
  3610.     jsr    emit
  3611.     clra
  3612.     rts
  3613.  
  3614. ;*case immed: epage(pnorm);
  3615. ;*        emit(baseop);
  3616. ;*        a = assarg();
  3617. ;*        if(a = 4) return(a);
  3618. ;*        emit(lobyte);
  3619. ;*        return(0);
  3620.  
  3621. dogimm:    ldaa    *pnorm
  3622.     jsr    epage
  3623.     ldaa    *baseop
  3624.     jsr    emit
  3625.     jsr    assarg
  3626.     cmpa    #0x04
  3627.     bne    dogimm1        ; jump if arg ok
  3628.     rts
  3629. dogimm1:
  3630.     ldaa    *shftreg+1
  3631.     jsr    emit
  3632.     clra
  3633.     rts
  3634.  
  3635. ;*case indy: epage(py);
  3636. ;*        a=doindex(op+0x20);
  3637. ;*        return(a);
  3638.  
  3639. dogindy:
  3640.     ldaa    *py
  3641.     jsr    epage
  3642.     ldaa    *baseop
  3643.     adda    #0x20
  3644.     staa    *baseop
  3645.     jsr    doindex
  3646.     rts
  3647.  
  3648. ;*case indx: epage(px);
  3649. ;*        a=doindex(op+0x20);
  3650. ;*        return(a);
  3651.  
  3652. dogindx:
  3653.     ldaa    *px
  3654.     jsr    epage
  3655.     ldaa    *baseop
  3656.     adda    #0x20
  3657.     staa    *baseop
  3658.     jsr    doindex
  3659.     rts
  3660.  
  3661. ;*case other: a = assarg();
  3662. ;*        if(a = 4) return(a);
  3663. ;*        epage(pnorm);
  3664. ;*        if(countu1 <= 2 digits)    /* direct */
  3665. ;*        emit(op+0x10);
  3666. ;*        emit(lobyte(result));
  3667. ;*        return(0);
  3668. ;*        else    emit(op+0x30);    /* extended */
  3669. ;*        eword(result);
  3670. ;*        return(0)
  3671.  
  3672. dogoth:    jsr    assarg
  3673.     cmpa    #0x04
  3674.     bne    dogoth0        ; jump if arg ok
  3675.     rts
  3676. dogoth0:
  3677.     ldaa    *pnorm
  3678.     jsr    epage
  3679.     ldaa    *count
  3680.     cmpa    #0x2
  3681.     bgt    dogoth1
  3682.     ldaa    *baseop
  3683.     adda    #0x10        ; direct mode opcode
  3684.     jsr    emit
  3685.     ldaa    *shftreg+1
  3686.     jsr    emit
  3687.     clra
  3688.     rts
  3689. dogoth1:
  3690.     ldaa    *baseop
  3691.     adda    #0x30        ; extended mode opcode
  3692.     jsr    emit
  3693.     ldd    *shftreg
  3694.     jsr    emit
  3695.     tba
  3696.     jsr    emit
  3697.     clra
  3698.     rts
  3699.  
  3700. ;**********
  3701. ;**    doindex(op) --- handle all wierd stuff for
  3702. ;**    indexed addressing. returns a = error number.
  3703. ;**********
  3704. ;*emit(baseop);
  3705. ;*a=assarg();
  3706. ;*if(a = 4) return(a);
  3707. ;*if( a != ',' ) return("syntax");
  3708. ;*buffptr++
  3709. ;*a=readbuff()
  3710. ;*if( a != 'x' && != 'y') warn("ind addr assumed");
  3711. ;*emit(lobyte);
  3712. ;*return(0);
  3713.  
  3714. doindex:
  3715.     ldaa    *baseop
  3716.     jsr    emit
  3717.     jsr    assarg
  3718.     cmpa    #0x04
  3719.     bne    doindx0        ; jump if arg ok
  3720.     rts
  3721. doindx0:
  3722.     cmpa    #',
  3723.     beq    doindx1
  3724.     ldaa    #0x08        ; "syntax error"
  3725.     rts
  3726. doindx1:
  3727.     jsr    incbuff
  3728.     jsr    readbuff
  3729.     cmpa    #'Y
  3730.     beq    doindx2
  3731.     cmpa    #'X
  3732.     beq    doindx2
  3733.     ldx    msga7        ; "index addr assumed"
  3734.     jsr    outstrg
  3735. doindx2:
  3736.     ldaa    *shftreg+1
  3737.     jsr    emit
  3738.     clra
  3739.     rts
  3740.  
  3741. ;**********
  3742. ;**    assarg(); - get argument.    returns a = 4 if bad
  3743. ;** argument, else a = first non hex char.
  3744. ;**********
  3745. ;*a = buffarg()
  3746. ;*if(asschk(aa) && countu1 != 0) return(a);
  3747. ;*return(bad argument);
  3748.  
  3749. assarg:    jsr    buffarg
  3750.     jsr    asschek        ; check for command
  3751.     beq    assarg1        ; jump if ok
  3752.     jsr    wchek        ; check for whitespace
  3753.     bne    assarg2        ; jump if not ok
  3754. assarg1:
  3755.     tst    *count
  3756.     beq    assarg2        ; jump if no argument
  3757.     rts
  3758. assarg2:
  3759.     ldaa    #0x04        ; bad argument
  3760.     rts
  3761.  
  3762. ;**********
  3763. ;**  epage(a) --- emit page prebyte
  3764. ;**********
  3765. ;*if( a != page1 ) emit(a);
  3766.  
  3767. epage:    cmpa    #page1
  3768.     beq    epagrt        ; jump if page 1
  3769.     jsr    emit
  3770. epagrt:    rts
  3771.  
  3772. ;**********
  3773. ;*    emit(a) --- emit contents of a
  3774. ;**********
  3775. emit:    ldx    *pc
  3776.     staa    0,x
  3777.     jsr    out1bsp
  3778.     stx    *pc
  3779.     rts
  3780.  
  3781. ;*mnemonic table for hc11 line assembler
  3782. null    =    0x0        ; nothing
  3783. inh    =    0x1        ; inherent
  3784. p2inh    =    0x2        ; page 2 inherent
  3785. gen    =    0x3        ; general addressing
  3786. grp2    =    0x4        ; group 2
  3787. rel    =    0x5        ; relative
  3788. imm    =    0x6        ; immediate
  3789. nimm    =    0x7        ; general except for immediate
  3790. limm    =    0x8        ; 2 byte immediate
  3791. xlimm    =    0x9        ; longimm for x
  3792. xnimm    =    0x10        ; no immediate for x
  3793. ylimm    =    0x11        ; longimm for y
  3794. ynimm    =    0x12        ; no immediate for y
  3795. btb    =    0x13        ; bit test and branch
  3796. setclr    =    0x14        ; bit set or clear
  3797. cpd    =    0x15        ; compare d
  3798. btbd    =    0x16        ; bit test and branch direct
  3799. setclrd    =    0x17        ; bit set or clear direct
  3800.  
  3801. ;**********
  3802. ;*    mnetabl - includes all '11 mnemonics, base opcodes,
  3803. ;* and type of instruction.  the assembler search routine
  3804. ;*depends on 4 characters for each mnemonic so that 3 char
  3805. ;*mnemonics are extended with a space and 5 char mnemonics
  3806. ;*are truncated.
  3807. ;**********
  3808.  
  3809. mnetabl    = .
  3810.     .ascii    'ABA '        ; mnemonic
  3811.     .byte    0x1b        ; base opcode
  3812.     .byte    inh        ; class
  3813.     .ascii    'ABX '
  3814.     .byte    0x3a
  3815.     .byte    inh
  3816.     .ascii    'ABY '
  3817.     .byte    0x3a
  3818.     .byte    p2inh
  3819.     .ascii    'ADCA'
  3820.     .byte    0x89
  3821.     .byte    gen
  3822.     .ascii    'ADCB'
  3823.     .byte    0xc9
  3824.     .byte    gen
  3825.     .ascii    'ADDA'
  3826.     .byte    0x8b
  3827.     .byte    gen
  3828.     .ascii    'ADDB'
  3829.     .byte    0xcb
  3830.     .byte    gen
  3831.     .ascii    'ADDD'
  3832.     .byte    0xc3
  3833.     .byte    limm
  3834.     .ascii    'ANDA'
  3835.     .byte    0x84
  3836.     .byte    gen
  3837.     .ascii    'ANDB'
  3838.     .byte    0xc4
  3839.     .byte    gen
  3840.     .ascii    'ASL '
  3841.     .byte    0x68
  3842.     .byte    grp2
  3843.     .ascii    'ASLA'
  3844.     .byte    0x48
  3845.     .byte    inh
  3846.     .ascii    'ASLB'
  3847.     .byte    0x58
  3848.     .byte    inh
  3849.     .ascii    'ASLD'
  3850.     .byte    0x05
  3851.     .byte    inh
  3852.     .ascii    'ASR '
  3853.     .byte    0x67
  3854.     .byte    grp2
  3855.     .ascii    'ASRA'
  3856.     .byte    0x47
  3857.     .byte    inh
  3858.     .ascii    'ASRB'
  3859.     .byte    0x57
  3860.     .byte    inh
  3861.     .ascii    'BCC '
  3862.     .byte    0x24
  3863.     .byte    rel
  3864.     .ascii    'BCLR'
  3865.     .byte    0x1d
  3866.     .byte    setclr
  3867.     .ascii    'BCS '
  3868.     .byte    0x25
  3869.     .byte    rel
  3870.     .ascii    'BEQ '
  3871.     .byte    0x27
  3872.     .byte    rel
  3873.     .ascii    'BGE '
  3874.     .byte    0x2c
  3875.     .byte    rel
  3876.     .ascii    'BGT '
  3877.     .byte    0x2e
  3878.     .byte    rel
  3879.     .ascii    'BHI '
  3880.     .byte    0x22
  3881.     .byte    rel
  3882.     .ascii    'BHS '
  3883.     .byte    0x24
  3884.     .byte    rel
  3885.     .ascii    'BITA'
  3886.     .byte    0x85
  3887.     .byte    gen
  3888.     .ascii    'BITB'
  3889.     .byte    0xc5
  3890.     .byte    gen
  3891.     .ascii    'BLE '
  3892.     .byte    0x2f
  3893.     .byte    rel
  3894.     .ascii    'BLO '
  3895.     .byte    0x25
  3896.     .byte    rel
  3897.     .ascii    'BLS '
  3898.     .byte    0x23
  3899.     .byte    rel
  3900.     .ascii    'BLT '
  3901.     .byte    0x2d
  3902.     .byte    rel
  3903.     .ascii    'BMI '
  3904.     .byte    0x2b
  3905.     .byte    rel
  3906.     .ascii    'BNE '
  3907.     .byte    0x26
  3908.     .byte    rel
  3909.     .ascii    'BPL '
  3910.     .byte    0x2a
  3911.     .byte    rel
  3912.     .ascii    'BRA '
  3913.     .byte    0x20
  3914.     .byte    rel
  3915.     .ascii    'BRCL'        ; (brclr)
  3916.     .byte    0x1f
  3917.     .byte    btb
  3918.     .ascii    'BRN '
  3919.     .byte    0x21
  3920.     .byte    rel
  3921.     .ascii    'BRSE'        ; (brset)
  3922.     .byte    0x1e
  3923.     .byte    btb
  3924.     .ascii    'BSET'
  3925.     .byte    0x1c
  3926.     .byte    setclr
  3927.     .ascii    'BSR '
  3928.     .byte    0x8d
  3929.     .byte    rel
  3930.     .ascii    'BVC '
  3931.     .byte    0x28
  3932.     .byte    rel
  3933.     .ascii    'BVS '
  3934.     .byte    0x29
  3935.     .byte    rel
  3936.     .ascii    'CBA '
  3937.     .byte    0x11
  3938.     .byte    inh
  3939.     .ascii    'CLC '
  3940.     .byte    0x0c
  3941.     .byte    inh
  3942.     .ascii    'CLI '
  3943.     .byte    0x0e
  3944.     .byte    inh
  3945.     .ascii    'CLR '
  3946.     .byte    0x6f
  3947.     .byte    grp2
  3948.     .ascii    'CLRA'
  3949.     .byte    0x4f
  3950.     .byte    inh
  3951.     .ascii    'CLRB'
  3952.     .byte    0x5f
  3953.     .byte    inh
  3954.     .ascii    'CLV '
  3955.     .byte    0x0a
  3956.     .byte    inh
  3957.     .ascii    'CMPA'
  3958.     .byte    0x81
  3959.     .byte    gen
  3960.     .ascii    'CMPB'
  3961.     .byte    0xc1
  3962.     .byte    gen
  3963.     .ascii    'COM '
  3964.     .byte    0x63
  3965.     .byte    grp2
  3966.     .ascii    'COMA'
  3967.     .byte    0x43
  3968.     .byte    inh
  3969.     .ascii    'COMB'
  3970.     .byte    0x53
  3971.     .byte    inh
  3972.     .ascii    'CPD '
  3973.     .byte    0x83
  3974.     .byte    cpd
  3975.     .ascii    'CPX '
  3976.     .byte    0x8c
  3977.     .byte    xlimm
  3978.     .ascii    'CPY '
  3979.     .byte    0x8c
  3980.     .byte    ylimm
  3981.     .ascii    'DAA '
  3982.     .byte    0x19
  3983.     .byte    inh
  3984.     .ascii    'DEC '
  3985.     .byte    0x6a
  3986.     .byte    grp2
  3987.     .ascii    'DECA'
  3988.     .byte    0x4a
  3989.     .byte    inh
  3990.     .ascii    'DECB'
  3991.     .byte    0x5a
  3992.     .byte    inh
  3993.     .ascii    'DES '
  3994.     .byte    0x34
  3995.     .byte    inh
  3996.     .ascii    'DEX '
  3997.     .byte    0x09
  3998.     .byte    inh
  3999.     .ascii    'DEY '
  4000.     .byte    0x09
  4001.     .byte    p2inh
  4002.     .ascii    'EORA'
  4003.     .byte    0x88
  4004.     .byte    gen
  4005.     .ascii    'EORB'
  4006.     .byte    0xc8
  4007.     .byte    gen
  4008.     .ascii    'FDIV'
  4009.     .byte    0x03
  4010.     .byte    inh
  4011.     .ascii    'IDIV'
  4012.     .byte    0x02
  4013.     .byte    inh
  4014.     .ascii    'INC '
  4015.     .byte    0x6c
  4016.     .byte    grp2
  4017.     .ascii    'INCA'
  4018.     .byte    0x4c
  4019.     .byte    inh
  4020.     .ascii    'INCB'
  4021.     .byte    0x5c
  4022.     .byte    inh
  4023.     .ascii    'INS '
  4024.     .byte    0x31
  4025.     .byte    inh
  4026.     .ascii    'INX '
  4027.     .byte    0x08
  4028.     .byte    inh
  4029.     .ascii    'INY '
  4030.     .byte    0x08
  4031.     .byte    p2inh
  4032.     .ascii    'JMP '
  4033.     .byte    0x6e
  4034.     .byte    grp2
  4035.     .ascii    'JSR '
  4036.     .byte    0x8d
  4037.     .byte    nimm
  4038.     .ascii    'LDAA'
  4039.     .byte    0x86
  4040.     .byte    gen
  4041.     .ascii    'LDAB'
  4042.     .byte    0xc6
  4043.     .byte    gen
  4044.     .ascii    'LDD '
  4045.     .byte    0xcc
  4046.     .byte    limm
  4047.     .ascii    'LDS '
  4048.     .byte    0x8e
  4049.     .byte    limm
  4050.     .ascii    'LDX '
  4051.     .byte    0xce
  4052.     .byte    xlimm
  4053.     .ascii    'LDY '
  4054.     .byte    0xce
  4055.     .byte    ylimm
  4056.     .ascii    'LSL '
  4057.     .byte    0x68
  4058.     .byte    grp2
  4059.     .ascii    'LSLA'
  4060.     .byte    0x48
  4061.     .byte    inh
  4062.     .ascii    'LSLB'
  4063.     .byte    0x58
  4064.     .byte    inh
  4065.     .ascii    'LSLD'
  4066.     .byte    0x05
  4067.     .byte    inh
  4068.     .ascii    'LSR '
  4069.     .byte    0x64
  4070.     .byte    grp2
  4071.     .ascii    'LSRA'
  4072.     .byte    0x44
  4073.     .byte    inh
  4074.     .ascii    'LSRB'
  4075.     .byte    0x54
  4076.     .byte    inh
  4077.     .ascii    'LSRD'
  4078.     .byte    0x04
  4079.     .byte    inh
  4080.     .ascii    'MUL '
  4081.     .byte    0x3d
  4082.     .byte    inh
  4083.     .ascii    'NEG '
  4084.     .byte    0x60
  4085.     .byte    grp2
  4086.     .ascii    'NEGA'
  4087.     .byte    0x40
  4088.     .byte    inh
  4089.     .ascii    'NEGB'
  4090.     .byte    0x50
  4091.     .byte    inh
  4092.     .ascii    'NOP '
  4093.     .byte    0x01
  4094.     .byte    inh
  4095.     .ascii    'ORAA'
  4096.     .byte    0x8a
  4097.     .byte    gen
  4098.     .ascii    'ORAB'
  4099.     .byte    0xca
  4100.     .byte    gen
  4101.     .ascii    'PSHA'
  4102.     .byte    0x36
  4103.     .byte    inh
  4104.     .ascii    'PSHB'
  4105.     .byte    0x37
  4106.     .byte    inh
  4107.     .ascii    'PSHX'
  4108.     .byte    0x3c
  4109.     .byte    inh
  4110.     .ascii    'PSHY'
  4111.     .byte    0x3c
  4112.     .byte    p2inh
  4113.     .ascii    'PULA'
  4114.     .byte    0x32
  4115.     .byte    inh
  4116.     .ascii    'PULB'
  4117.     .byte    0x33
  4118.     .byte    inh
  4119.     .ascii    'PULX'
  4120.     .byte    0x38
  4121.     .byte    inh
  4122.     .ascii    'PULY'
  4123.     .byte    0x38
  4124.     .byte    p2inh
  4125.     .ascii    'ROL '
  4126.     .byte    0x69
  4127.     .byte    grp2
  4128.     .ascii    'ROLA'
  4129.     .byte    0x49
  4130.     .byte    inh
  4131.     .ascii    'ROLB'
  4132.     .byte    0x59
  4133.     .byte    inh
  4134.     .ascii    'ROR '
  4135.     .byte    0x66
  4136.     .byte    grp2
  4137.     .ascii    'RORA'
  4138.     .byte    0x46
  4139.     .byte    inh
  4140.     .ascii    'RORB'
  4141.     .byte    0x56
  4142.     .byte    inh
  4143.     .ascii    'RTI '
  4144.     .byte    0x3b
  4145.     .byte    inh
  4146.     .ascii    'RTS '
  4147.     .byte    0x39
  4148.     .byte    inh
  4149.     .ascii    'SBA '
  4150.     .byte    0x10
  4151.     .byte    inh
  4152.     .ascii    'SBCA'
  4153.     .byte    0x82
  4154.     .byte    gen
  4155.     .ascii    'SBCB'
  4156.     .byte    0xc2
  4157.     .byte    gen
  4158.     .ascii    'SEC '
  4159.     .byte    0x0d
  4160.     .byte    inh
  4161.     .ascii    'SEI '
  4162.     .byte    0x0f
  4163.     .byte    inh
  4164.     .ascii    'SEV '
  4165.     .byte    0x0b
  4166.     .byte    inh
  4167.     .ascii    'STAA'
  4168.     .byte    0x87
  4169.     .byte    nimm
  4170.     .ascii    'STAB'
  4171.     .byte    0xc7
  4172.     .byte    nimm
  4173.     .ascii    'STD '
  4174.     .byte    0xcd
  4175.     .byte    nimm
  4176.     .ascii    'STOP'
  4177.     .byte    0xcf
  4178.     .byte    inh
  4179.     .ascii    'STS '
  4180.     .byte    0x8f
  4181.     .byte    nimm
  4182.     .ascii    'STX '
  4183.     .byte    0xcf
  4184.     .byte    xnimm
  4185.     .ascii    'STY '
  4186.     .byte    0xcf
  4187.     .byte    ynimm
  4188.     .ascii    'SUBA'
  4189.     .byte    0x80
  4190.     .byte    gen
  4191.     .ascii    'SUBB'
  4192.     .byte    0xc0
  4193.     .byte    gen
  4194.     .ascii    'SUBD'
  4195.     .byte    0x83
  4196.     .byte    limm
  4197.     .ascii    'SWI '
  4198.     .byte    0x3f
  4199.     .byte    inh
  4200.     .ascii    'TAB '
  4201.     .byte    0x16
  4202.     .byte    inh
  4203.     .ascii    'TAP '
  4204.     .byte    0x06
  4205.     .byte    inh
  4206.     .ascii    'TBA '
  4207.     .byte    0x17
  4208.     .byte    inh
  4209.     .ascii    'TPA '
  4210.     .byte    0x07
  4211.     .byte    inh
  4212.     .ascii    'TEST'
  4213.     .byte    0x00
  4214.     .byte    inh
  4215.     .ascii    'TST '
  4216.     .byte    0x6d
  4217.     .byte    grp2
  4218.     .ascii    'TSTA'
  4219.     .byte    0x4d
  4220.     .byte    inh
  4221.     .ascii    'TSTB'
  4222.     .byte    0x5d
  4223.     .byte    inh
  4224.     .ascii    'TSX '
  4225.     .byte    0x30
  4226.     .byte    inh
  4227.     .ascii    'TSY '
  4228.     .byte    0x30
  4229.     .byte    p2inh
  4230.     .ascii    'TXS '
  4231.     .byte    0x35
  4232.     .byte    inh
  4233.     .ascii    'TYS '
  4234.     .byte    0x35
  4235.     .byte    p2inh
  4236.     .ascii    'WAI '
  4237.     .byte    0x3e
  4238.     .byte    inh
  4239.     .ascii    'XGDX'
  4240.     .byte    0x8f
  4241.     .byte    inh
  4242.     .ascii    'XGDY'
  4243.     .byte    0x8f
  4244.     .byte    p2inh
  4245.     .ascii    'BRSE'        ; bit direct modes for
  4246.     .byte    0x12        ; disassembler.
  4247.     .byte    btbd
  4248.     .ascii    'BRCL'
  4249.     .byte    0x13
  4250.     .byte    btbd
  4251.     .ascii    'BSET'
  4252.     .byte    0x14
  4253.     .byte    setclrd
  4254.     .ascii    'BCLR'
  4255.     .byte    0x15
  4256.     .byte    setclrd
  4257.     .byte    eot        ; end of table
  4258.  
  4259. ;**********************************************
  4260. pg1    =    0x0
  4261. pg2    =    0x1
  4262. pg3    =    0x2
  4263. pg4    =    0x3
  4264.  
  4265. ;******************
  4266. ;*disassem() - disassemble the opcode.
  4267. ;******************
  4268. ;*(check for page prebyte)
  4269. ;*baseop=pc[0];
  4270. ;*pnorm=pg1;
  4271. ;*if(baseop==0x18) pnorm=pg2;
  4272. ;*if(baseop==0x1a) pnorm=pg3;
  4273. ;*if(baseop==0xcd) pnorm=pg4;
  4274. ;*if(pnorm != pg1) dispc=pc+1;
  4275. ;*else dispc=pc; (dispc points to next byte)
  4276.  
  4277. disassm    = .
  4278.     ldx    *pc         ; address
  4279.     ldaa    0,x        ; opcode
  4280.     ldab    #pg1
  4281.     cmpa    #0x18
  4282.     beq    disp2        ; jump if page2
  4283.     cmpa    #0x1a
  4284.     beq    disp3        ; jump if page3
  4285.     cmpa    #0xcd
  4286.     bne    disp1        ; jump if not page4
  4287. disp4:    incb            ; set up page value
  4288. disp3:    incb
  4289. disp2:    incb
  4290.     inx
  4291. disp1:    stx    *dispc        ; point to opcode
  4292.     stab    *pnorm        ; save page
  4293.  
  4294. ;*if(opcode == (0x00-0x5f or 0x8d or 0x8f or 0xcf))
  4295. ;*    if(pnorm == (pg3 or pg4))
  4296. ;*    disillop(); return();
  4297. ;*  b=disrch(opcode,null);
  4298. ;*  if(b==0) disillop(); return();
  4299.  
  4300.     ldaa    0,x        ; get current opcode
  4301.     staa    *baseop
  4302.     inx
  4303.     stx    *dispc        ; point to next byte
  4304.     cmpa    #0x5f
  4305.     bls    dis1        ; jump if in range
  4306.     cmpa    #0x8d
  4307.     beq    dis1        ; jump if bsr
  4308.     cmpa    #0x8f
  4309.     beq    dis1        ; jump if xgdx
  4310.     cmpa    #0xcf
  4311.     beq    dis1        ; jump if stop
  4312.     jmp    disgrp        ; try next part of map
  4313. dis1:    ldab    *pnorm
  4314.     cmpb    #pg3
  4315.     blo    dis2        ; jump if page 1 or 2
  4316.     jsr    disillop    ; "illegal opcode"
  4317.     rts
  4318. dis2:    ldab    *baseop        ; opcode
  4319.     clrb            ; class=null
  4320.     jsr    disrch
  4321.     tstb
  4322.     bne    dispec        ; jump if opcode found
  4323.     jsr    disillop    ; "illegal opcode"
  4324.     rts
  4325.  
  4326. ;*    if(opcode==0x8d) dissrch(opcode,rel);
  4327. ;*    if(opcode==(0x8f or 0xcf)) disrch(opcode,inh);
  4328.  
  4329. dispec:    ldaa    *baseop
  4330.     cmpa    #0x8d
  4331.     bne    dispec1
  4332.     ldab    #rel
  4333.     bra    dispec3        ; look for bsr opcode
  4334. dispec1:
  4335.     cmpa    #0x8f
  4336.     beq    dispec2        ; jump if xgdx opcode
  4337.     cmpa    #0xcf
  4338.     bne    disinh        ; jump not stop opcode
  4339. dispec2:
  4340.     ldab    #inh
  4341. dispec3:
  4342.     jsr    disrch        ; find other entry in table
  4343.  
  4344. ;*    if(class==inh)        /* inh */
  4345. ;*    if(pnorm==pg2)
  4346. ;*    b=disrch(baseop,p2inh);
  4347. ;*    if(b==0) disillop(); return();
  4348. ;*    prntmne();
  4349. ;*    return();
  4350.  
  4351. disinh    = .
  4352.     ldab    *class
  4353.     cmpb    #inh
  4354.     bne    disrel        ; jump if not inherent
  4355.     ldab    *pnorm
  4356.     cmpb    #pg1
  4357.     beq    disinh1        ; jump if page1
  4358.     ldaa    *baseop        ; get opcode
  4359.     ldab    #p2inh        ; class=p2inh
  4360.     jsr    disrch
  4361.     tstb
  4362.     bne    disinh1        ; jump if found
  4363.     jsr    disillop    ; "illegal opcode"
  4364.     rts
  4365. disinh1:
  4366.     jsr    prntmne
  4367.     rts
  4368.  
  4369. ;*    elseif(class=rel)        /* rel */
  4370. ;*    if(pnorm != pg1)
  4371. ;*    disillop(); return();
  4372. ;*    prntmne();
  4373. ;*    disrelad();
  4374. ;*    return();
  4375.  
  4376. disrel    = .
  4377.     ldab    *class
  4378.     cmpb    #rel
  4379.     bne    disbtd
  4380.     tst    *pnorm
  4381.     beq    disrel1        ; jump if page1
  4382.     jsr    disillop    ; "illegal opcode"
  4383.     rts
  4384. disrel1:
  4385.     jsr    prntmne        ; output mnemonic
  4386.     jsr    disrelad    ; compute relative address
  4387.     rts
  4388.  
  4389. ;*    else        /* setclr,setclrd,btb,btbd */
  4390. ;*    if(class == (setclrd or btbd))
  4391. ;*        if(pnorm != pg1)
  4392. ;*        disillop(); return();    /* illop */
  4393. ;*        prntmne();        /* direct */
  4394. ;*        disdir();        /* output 0xbyte */
  4395. ;*    else (class == (setclr or btb))
  4396. ;*        prntmne();        /* indexed */
  4397. ;*        disindx();
  4398. ;*    outspac();
  4399. ;*    disdir();
  4400. ;*    outspac();
  4401. ;*    if(class == (btb or btbd))
  4402. ;*        disrelad();
  4403. ;*    return();
  4404.  
  4405. disbtd    = .
  4406.     ldab    *class
  4407.     cmpb    #setclrd
  4408.     beq    disbtd1
  4409.     cmpb    #btbd
  4410.     bne    disbit        ; jump not direct bitop
  4411. disbtd1:
  4412.     tst    *pnorm
  4413.     beq    disbtd2        ; jump if page 1
  4414.     jsr    disillop
  4415.     rts
  4416. disbtd2:
  4417.     jsr    prntmne
  4418.     jsr    disdir        ; operand(direct)
  4419.     bra    disbit1
  4420. disbit    = .
  4421.     jsr    prntmne
  4422.     jsr    disindx        ; operand(indexed)
  4423. disbit1:
  4424.     jsr    outspac
  4425.     jsr    disdir        ; mask
  4426.     ldab    *class
  4427.     cmpb    #btb
  4428.     beq    disbit2        ; jump if btb
  4429.     cmpb    #btbd
  4430.     bne    disbit3        ; jump if not bit branch
  4431. disbit2:
  4432.     jsr    disrelad    ; relative address
  4433. disbit3:
  4434.     rts
  4435.  
  4436.  
  4437. ;*elseif(0x60 <= opcode <= 0x7f)  /*  grp2 */
  4438. ;*    if(pnorm == (pg3 or pg4))
  4439. ;*    disillop(); return();
  4440. ;*    if((pnorm==pg2) and (opcode != 0x6x))
  4441. ;*    disillop(); return();
  4442. ;*    b=disrch(baseop & 0x6f,null);
  4443. ;*    if(b==0) disillop(); return();
  4444. ;*    prntmne();
  4445. ;*    if(opcode == 0x6x)
  4446. ;*    disindx();
  4447. ;*    else
  4448. ;*    disext();
  4449. ;*    return();
  4450.  
  4451. disgrp    = .
  4452.     cmpa    #0x7f        ; a=opcode
  4453.     bhi    disnext        ; try next part of map
  4454.     ldab    *pnorm
  4455.     cmpb    #pg3
  4456.     blo    disgrp2        ; jump if page 1 or 2
  4457.     jsr    disillop    ; "illegal opcode"
  4458.     rts
  4459. disgrp2:
  4460.     anda    #0x6f        ; mask bit 4
  4461.     clrb            ; class=null
  4462.     jsr    disrch
  4463.     tstb
  4464.     bne    disgrp3        ; jump if found
  4465.     jsr    disillop    ; "illegal opcode"
  4466.     rts
  4467. disgrp3:
  4468.     jsr    prntmne
  4469.     ldaa    *baseop        ; get opcode
  4470.     anda    #0xf0
  4471.     cmpa    #0x60
  4472.     bne    disgrp4        ; jump if not 6x
  4473.     jsr    disindx        ; operand(indexed)
  4474.     rts
  4475. disgrp4:
  4476.     jsr    disext        ; operand(extended)
  4477.     rts
  4478.  
  4479. ;*else    (0x80 <= opcode <= 0xff)
  4480. ;*    if(opcode == (0x87 or 0xc7))
  4481. ;*    disillop(); return();
  4482. ;*    b=disrch(opcode&0xcf,null);
  4483. ;*    if(b==0) disillop(); return();
  4484.  
  4485. disnext    = .
  4486.     cmpa    #0x87        ; a=opcode
  4487.     beq    disnex1
  4488.     cmpa    #0xc7
  4489.     bne    disnex2
  4490. disnex1:
  4491.     jsr    disillop    ; "illegal opcode"
  4492.     rts
  4493. disnex2:
  4494.     anda    #0xcf
  4495.     clrb            ; class=null
  4496.     jsr    disrch
  4497.     tstb
  4498.     bne    disnew        ; jump if mne found
  4499.     jsr    disillop    ; "illegal opcode"
  4500.     rts
  4501.  
  4502. ;*    if(opcode&0xcf==0x8d) disrch(baseop,nimm; (jsr)
  4503. ;*    if(opcode&0xcf==0x8f) disrch(baseop,nimm; (sts)
  4504. ;*    if(opcode&0xcf==0xcf) disrch(baseop,xnimm; (stx)
  4505. ;*    if(opcode&0xcf==0x83) disrch(baseop,limm); (subd)
  4506.  
  4507. disnew:    ldaa    *baseop
  4508.     anda    #0xcf
  4509.     cmpa    #0x8d
  4510.     bne    disnew1        ; jump not jsr
  4511.     ldab    #nimm
  4512.     bra    disnew4
  4513. disnew1:
  4514.     cmpa    #0x8f
  4515.     bne    disnew2        ; jump not sts
  4516.     ldab    #nimm
  4517.     bra    disnew4
  4518. disnew2:
  4519.     cmpa    #0xcf
  4520.     bne    disnew3        ; jump not stx
  4521.     ldab    #xnimm
  4522.     bra    disnew4
  4523. disnew3:
  4524.     cmpa    #0x83
  4525.     bne    disgen        ; jump not subd
  4526.     ldab    #limm
  4527. disnew4:
  4528.     jsr    disrch
  4529.     tstb
  4530.     bne    disgen        ; jump if found
  4531.     jsr    disillop    ; "illegal opcode"
  4532.     rts
  4533.  
  4534. ;*    if(class == (gen or nimm or limm    ))    /* gen,nimm,limm,cpd */
  4535. ;*    if(opcode&0xcf==0x83)
  4536. ;*        if(pnorm==(pg3 or pg4)) disrch(opcode#0xcf,cpd)
  4537. ;*        class=limm;
  4538. ;*    if((pnorm == (pg2 or pg4) and (opcode != (0xax or 0xex)))
  4539. ;*        disillop(); return();
  4540. ;*    disgenrl();
  4541. ;*    return();
  4542.  
  4543. disgen:    ldab    *class        ; get class
  4544.     cmpb    #gen
  4545.     beq    disgen1
  4546.     cmpb    #nimm
  4547.     beq    disgen1
  4548.     cmpb    #limm
  4549.     bne    disxln        ; jump if other class
  4550. disgen1:
  4551.     ldaa    *baseop
  4552.     anda    #0xcf
  4553.     cmpa    #0x83
  4554.     bne    disgen3        ; jump if not    #0x83
  4555.     ldab    *pnorm
  4556.     cmpb    #pg3
  4557.     blo    disgen3        ; jump not pg3 or 4
  4558.     ldab    #cpd
  4559.     jsr    disrch        ; look for cpd mne
  4560.     ldab    #limm
  4561.     stab    *class        ; set class to limm
  4562. disgen3:
  4563.     ldab    *pnorm
  4564.     cmpb    #pg2
  4565.     beq    disgen4        ; jump if page 2
  4566.     cmpb    #pg4
  4567.     bne    #disgen5    ; jump not page 2 or 4
  4568. disgen4:
  4569.     ldaa    *baseop
  4570.     anda    #0xb0        ; mask bits 6,3-0
  4571.     cmpa    #0xa0
  4572.     beq    disgen5        ; jump if 0xax or 0xex
  4573.     jsr    disillop    ; "illegal opcode"
  4574.     rts
  4575. disgen5:
  4576.     jsr    disgenrl    ; process general class
  4577.     rts
  4578.  
  4579. ;*    else    /* xlimm,xnimm,ylimm,ynimm */
  4580. ;*    if(pnorm==(pg2 or pg3))
  4581. ;*    if(class==xlimm) disrch(opcode&0xcf,ylimm);
  4582. ;*    else disrch(opcode&0xcf,ynimm);
  4583. ;*    if((pnorm == (pg3 or pg4))
  4584. ;*    if(opcode != (0xax or 0xex))
  4585. ;*        disillop(); return();
  4586. ;*    class=limm;
  4587. ;*    disgen();
  4588. ;*    return();
  4589.  
  4590. disxln:    ldab    *pnorm
  4591.     cmpb    #pg2
  4592.     beq    disxln1        ; jump if page2
  4593.     cmpb    #pg3
  4594.     bne    disxln4        ; jump not page3
  4595. disxln1:
  4596.     ldaa    *baseop
  4597.     anda    #0xcf
  4598.     ldab    *class
  4599.     cmpb    #xlimm
  4600.     bne    disxln2
  4601.     ldab    #ylimm
  4602.     bra    disxln3        ; look for ylimm
  4603. disxln2:
  4604.     ldab    #ynimm        ; look for ynimm
  4605. disxln3:
  4606.     jsr    disrch
  4607. disxln4:
  4608.     ldab    *pnorm
  4609.     cmpb    #pg3
  4610.     blo    disxln5        ; jump if page 1 or 2
  4611.     ldaa    *baseop        ; get opcode
  4612.     anda    #0xb0        ; mask bits 6,3-0
  4613.     cmpa    #0xa0
  4614.     beq    disxln5        ; jump opcode = 0xax or 0xex
  4615.     jsr    disillop    ; "illegal opcode"
  4616.     rts
  4617. disxln5:
  4618.     ldab    #limm
  4619.     stab    *class
  4620.     jsr    disgenrl    ; process general class
  4621.     rts
  4622.  
  4623.  
  4624. ;******************
  4625. ;*disrch(a=opcode,b=class)
  4626. ;*return b=0 if not found
  4627. ;*    else mneptr=points to mnemonic
  4628. ;*    class=class of opcode
  4629. ;******************
  4630. ;*x=#mnetabl
  4631. ;*while(x[0] != eot)
  4632. ;*    if((opcode==x[4]) && ((class=null) || (class=x[5])))
  4633. ;*    mneptr=x;
  4634. ;*    class=x[5];
  4635. ;*    return(1);
  4636. ;*    x += 6;
  4637. ;*return(0);    /* not found */
  4638.  
  4639. disrch    = .
  4640.     ldx    #mnetabl    ; point to top of table
  4641. disrch1:
  4642.     cmpa    4,x        ; test opcode
  4643.     bne    disrch3        ; jump not this entry
  4644.     tstb
  4645.     beq    disrch2        ; jump if class=null
  4646.     cmpb    5,x        ; test class
  4647.     bne    disrch3        ; jump not this entry
  4648. disrch2:
  4649.     ldab    5,x
  4650.     stab    *class
  4651.     stx    *mneptr        ; return ptr to mnemonic
  4652.     incb
  4653.     rts            ; return found
  4654. disrch3:
  4655.     pshb            ; save class
  4656.     ldab    #6
  4657.     abx
  4658.     ldab    0,x
  4659.     cmpb    #eot        ; test end of table
  4660.     pulb
  4661.     bne    disrch1
  4662.     clrb
  4663.     rts            ; return not found
  4664.  
  4665. ;******************
  4666. ;*prntmne() - output the mnemonic pointed
  4667. ;*at by mneptr.
  4668. ;******************
  4669. ;*outa(mneptr[0-3]);
  4670. ;*outspac;
  4671. ;*return();
  4672.  
  4673. prntmne    = .
  4674.     ldx    *mneptr
  4675.     ldaa    0,x
  4676.     jsr    outa        ; output char1
  4677.     ldaa    1,x
  4678.     jsr    outa        ; output char2
  4679.     ldaa    2,x
  4680.     jsr    outa        ; output char3
  4681.     ldaa    3,x
  4682.     jsr    outa        ; output char4
  4683.     jsr    outspac
  4684.     rts
  4685.  
  4686. ;******************
  4687. ;*disindx() - process indexed mode
  4688. ;******************
  4689. ;*disdir();
  4690. ;*outa(',');
  4691. ;*if(pnorm == (pg2 or pg4)) outa('y');
  4692. ;*else outa('x');
  4693. ;*return();
  4694.  
  4695. disindx    = .
  4696.     jsr    disdir        ; output 0xbyte
  4697.     ldaa    #',
  4698.     jsr    outa        ; output ,
  4699.     ldab    *pnorm
  4700.     cmpb    #pg2
  4701.     beq    disind1        ; jump if page2
  4702.     cmpb    #pg4
  4703.     bne    disind2        ; jump if not page4
  4704. disind1:
  4705.     ldaa    #'Y
  4706.     bra disind3
  4707. disind2:
  4708.     ldaa    #'X
  4709. disind3:
  4710.     jsr    outa        ; output x or y
  4711.     rts
  4712.  
  4713. ;******************
  4714. ;*disrelad() - compute and output relative address.
  4715. ;******************
  4716. ;* braddr = dispc[0] + (dispc++);( 2's comp arith)
  4717. ;*outa('$');
  4718. ;*out2bsp(braddr);
  4719. ;*return();
  4720.  
  4721. disrelad    = .
  4722.     ldx    *dispc
  4723.     ldab    0,x        ; get relative offset
  4724.     inx
  4725.     stx    *dispc
  4726.     tstb
  4727.     bmi    disrld1        ; jump if negative
  4728.     abx
  4729.     bra    disrld2
  4730. disrld1:
  4731.     dex
  4732.     incb
  4733.     bne    disrld1        ; subtract
  4734. disrld2:
  4735.     stx    *braddr        ; save address
  4736.     jsr    outspac
  4737.     ldaa    #'$
  4738.     jsr    outa
  4739.     ldx    #braddr
  4740.     jsr    out2bsp        ; output address
  4741.     rts
  4742.  
  4743.  
  4744. ;******************
  4745. ;*disgenrl() - output data for the general cases which
  4746. ;*includes immediate, direct, indexed, and extended modes.
  4747. ;******************
  4748. ;*prntmne();
  4749. ;*if(baseop == (0x8x or 0xcx))    /* immediate */
  4750. ;*    outa('#');
  4751. ;*    disdir();
  4752. ;*    if(class == limm)
  4753. ;*    out1byt(dispc++);
  4754. ;*elseif(baseop == (0x9x or 0xdx))    /* direct */
  4755. ;*    disdir();
  4756. ;*elseif(baseop == (0xax or 0xex)) /* indexed */
  4757. ;*    disindx();
  4758. ;*else    (baseop == (0xbx or 0xfx)) /* extended */
  4759. ;*    disext();
  4760. ;*return();
  4761.  
  4762. disgenrl    = .
  4763.     jsr    prntmne        ; print mnemonic
  4764.     ldaa    *baseop        ; get opcode
  4765.     anda    #0xb0        ; mask bits 6,3-0
  4766.     cmpa    #0x80
  4767.     bne    disgrl2        ; jump if not immed
  4768.     ldaa    #'#        ; do immediate
  4769.     jsr    outa
  4770.     jsr    disdir
  4771.     ldab    *class
  4772.     cmpb    #limm
  4773.     beq    disgrl1        ; jump class = limm
  4774.     rts
  4775. disgrl1:
  4776.     ldx    *dispc
  4777.     jsr    out1byt
  4778.     stx    *dispc
  4779.     rts
  4780. disgrl2:
  4781.     cmpa    #0x90
  4782.     bne    disgrl3        ; jump not direct
  4783.     jsr    disdir        ; do direct
  4784.     rts
  4785. disgrl3:
  4786.     cmpa    #0xa0
  4787.     bne    disgrl4        ; jump not indexed
  4788.     jsr    disindx        ; do extended
  4789.     rts
  4790. disgrl4:
  4791.     jsr    disext        ; do extended
  4792.     rts
  4793.  
  4794. ;*****************
  4795. ;*disdir() - output "$ next byte"
  4796. ;*****************
  4797. disdir    = .
  4798.     ldaa    #'$
  4799.     jsr    outa
  4800.     ldx    *dispc
  4801.     jsr    out1byt
  4802.     stx    *dispc
  4803.     rts
  4804.  
  4805. ;*****************
  4806. ;*disext() - output "$ next 2 bytes"
  4807. ;*****************
  4808. disext    = .
  4809.     ldaa    #'$
  4810.     jsr    outa
  4811.     ldx    *dispc
  4812.     jsr    out2bsp
  4813.     stx    *dispc
  4814.     rts
  4815.  
  4816.  
  4817. ;*****************
  4818. ;*disillop() - output "illegal opcode"
  4819. ;*****************
  4820. dismsg1:
  4821.     .ascii    'ILLOP'
  4822.     .byte    eot
  4823. disillop    = .
  4824.     pshx
  4825.     ldx    #dismsg1
  4826.     jsr    outstrg0    ; no cr
  4827.     pulx
  4828.     rts
  4829.  
  4830. ;* equates
  4831. jportd    =    0x08
  4832. jddrd    =    0x09
  4833. jbaud    =    0x2b
  4834. jsccr1    =    0x2c
  4835. jsccr2    =    0x2d
  4836. jscsr    =    0x2e
  4837. jscdat    =    0x2f
  4838. ;*
  4839.  
  4840. ;************
  4841. ;*    boot [<addr>] - use sci to talk to an 'hc11 in
  4842. ;* boot mode.  downloads 256 bytes starting at addr.
  4843. ;* default addr = 0x2000.
  4844. ;************
  4845.  
  4846. ;*get arguments
  4847. ;*if no args, default 0x2000
  4848. boot:    jsr    wskip
  4849.     cmpa    #0x0d
  4850.     bne    bot1        ; jump if arguments
  4851.     ldy    #0x2000
  4852.     bra    bot2        ; go - use default address
  4853.  
  4854. ;*else get arguments
  4855. bot1:    jsr    buffarg
  4856.     tst    *count
  4857.     beq    boterr        ; jump if no address
  4858.     jsr    wskip
  4859.     ldy    *shftreg    ; start address
  4860.     cmpa    #0xd
  4861.     beq    bot2        ; go - use arguments
  4862. boterr:    ldx    #msg9        ; "bad argument"
  4863.     jsr    outstrg
  4864.     rts
  4865.  
  4866. ;*boot routine
  4867. bot2:    ldab    #0xff        ; control character (0xff -> download)
  4868.     jsr    btsub        ; set up sci and send control char
  4869.  
  4870. ;*download 256 byte block
  4871.     clrb            ; counter
  4872. blop:    ldaa    0,y
  4873.     staa    jscdat,x    ; write to transmitter
  4874.     iny
  4875.     brclr jscsr,x ,#0x80, .    ; wait for tdre
  4876.     decb
  4877.     bne    blop
  4878.     rts
  4879.  
  4880. ;************************************************
  4881. ;*subroutine
  4882. ;*    btsub    - sets up sci and outputs control character
  4883. ;* on entry, b = control character
  4884. ;* on exit,  x = 0x1000
  4885. ;*        a = 0x0c
  4886. ;***************************
  4887.  
  4888. btsub    = .
  4889.     ldx    #0x1000        ; to use indexed addressing
  4890.     ldaa    #0x02
  4891.     staa    jportd,x    ; drive transmitter line
  4892.     staa    jddrd,x        ; high
  4893.     clr    jsccr2,x    ; turn off xmtr and rcvr
  4894.     ldaa    #0x22        ; baud = /16
  4895.     staa    jbaud,x
  4896.     ldaa    #0x0c        ; turn on xmtr & rcvr
  4897.     staa    jsccr2,x
  4898.     stab    jscdat,x
  4899.     brclr jscsr,x ,#0x80, .    ; wait for tdre
  4900.     rts
  4901.  
  4902. ;******************
  4903. ;*
  4904. ;*    evbtest - this routine makes it a little easier
  4905. ;*    on us to test this board.
  4906. ;*
  4907. ;******************
  4908.  
  4909. evbtest:
  4910.     ldaa    #0xff
  4911.  
  4912.     staa    0x1000        ; write ones to port a
  4913.  
  4914.     clr    *autolf        ; turn off auto lf
  4915.     jsr    hostco        ; connect host
  4916.     jsr    hostinit    ; initialize host
  4917.  
  4918.     ldaa    #0x7f
  4919.     jsr    hostout        ; send delete to altos
  4920.     ldaa    #0x0d
  4921.     jsr    hostout        ; send <cr>
  4922.     inc    *autolf        ; turn on auto lf
  4923.     ldx    #inbuff+5    ; point at load message
  4924.     stx    *ptr0        ; set pointer for load command
  4925.     ldy    #msgevb        ; point at cat line
  4926. loop:    ldaa    0,y        ; loop to xfer command line
  4927.     cmpa    #04        ; into buffalo line buffer
  4928.     beq    done        ; quit on 0x04
  4929.     staa    0,x
  4930.     inx            ; next character
  4931.     iny
  4932.     bra    loop
  4933. done:    clr    *tmp2        ; set load vs. verify
  4934.     jsr    load1b        ; jmp into middle of load
  4935.     lds    #stack        ; reset stack
  4936.     jmp    0xc0b3        ; jump to downloaded code
  4937.  
  4938. msgevb:    .ascii    /cat evbtest.out/
  4939.     .byte    0x0d
  4940.     .byte    0x04
  4941.  
  4942.     .org    rombs+0x1fa0
  4943. ;*** jump table ***
  4944. .upcase:jmp    upcase
  4945. .wchek:    jmp    wchek
  4946. .dchek:    jmp    dchek
  4947. .init:    jmp    init
  4948. .input:    jmp    input
  4949. .output:jmp    output
  4950. .outlhl:jmp    outlhlf
  4951. .outrhl:jmp    outrhlf
  4952. .outa:    jmp    outa
  4953. .out1by:jmp    out1byt
  4954. .out1bs:jmp    out1bsp
  4955. .out2bs:jmp    out2bsp
  4956. .outcrl:jmp    outcrlf
  4957. .outstr:jmp    outstrg
  4958. .outst0:jmp    outstrg0
  4959. .inchar:jmp    inchar
  4960. .vecint:jmp    vecinit
  4961.  
  4962.     .org    rombs+0x1fd6
  4963. ;*** vectors ***
  4964. vsci:    .word    jsci
  4965. vspi:    .word    jspi
  4966. vpaie:    .word    jpaie
  4967. vpao:    .word    jpao
  4968. vtof:    .word    jtof
  4969. vtoc5:    .word    jtoc5
  4970. vtoc4:    .word    jtoc4
  4971. vtoc3:    .word    jtoc3
  4972. vtoc2:    .word    jtoc2
  4973. vtoc1:    .word    jtoc1
  4974. vtic3:    .word    jtic3
  4975. vtic2:    .word    jtic2
  4976. vtic1:    .word    jtic1
  4977. vrti:    .word    jrti
  4978. virq:    .word    jirq
  4979. vxirq:    .word    jxirq
  4980. vswi:    .word    jswi
  4981. villop:    .word    jillop
  4982. vcop:    .word    jcop
  4983. vclm:    .word    jclm
  4984. vrst:    .word    buffalo
  4985.  
  4986.